SmallInteger.st
changeset 701 a309e3ef7faf
parent 587 6b0b960020d5
child 809 5eef87c2907b
--- a/SmallInteger.st	Thu Dec 07 22:32:49 1995 +0100
+++ b/SmallInteger.st	Thu Dec 07 22:38:49 1995 +0100
@@ -11,10 +11,10 @@
 "
 
 Integer subclass:#SmallInteger
-       instanceVariableNames:''
-       classVariableNames:''
-       poolDictionaries:''
-       category:'Magnitude-Numbers'
+	 instanceVariableNames:''
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Magnitude-Numbers'
 !
 
 !SmallInteger class methodsFor:'documentation'!
@@ -33,10 +33,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libbasic/SmallInteger.st,v 1.39 1995-11-20 20:18:17 cg Exp $'
-!
-
 documentation
 "
     SmallIntegers are Integers in the range of at least +/- 2^30 
@@ -72,6 +68,34 @@
     self error:'instances of SmallInteger cannot be created with new'
 ! !
 
+!SmallInteger class methodsFor:'binary storage'!
+
+binaryDefinitionFrom: stream manager: manager
+    "read the binary representation as stored in storeBinaryOn:"
+
+    | value |
+
+    value := stream next bitAnd: 16r7F.
+    value > 16r3F ifTrue: [
+	value := value - 16r80
+    ].
+    value := (value bitShift: 8) bitOr: stream next.
+    value := (value bitShift: 8) bitOr: stream next.
+    value := (value bitShift: 8) bitOr: stream next.
+    ^ value
+! !
+
+!SmallInteger class methodsFor:'bit mask constants'!
+
+bitMaskFor:index
+    "return a bitmask for the index's bit (index starts at 1)"
+
+    (index between:1 and:SmallInteger maxBits) ifFalse:[
+	^ self error:'index out of bounds'
+    ].
+    ^ 1 bitShift:(index - 1)
+! !
+
 !SmallInteger class methodsFor:'constants'!
 
 maxBits
@@ -96,17 +120,6 @@
     "SmallInteger maxBytes"
 !
 
-minVal
-    "return the smallest Integer representable as SmallInteger.
-     For very special uses only - not constant across implementations"
-
-%{  /* NOCONTEXT */
-    RETURN ( _MKSMALLINT(_MIN_INT) );
-%}
-
-    "SmallInteger minVal"
-!
-
 maxVal
     "return the largest Integer representable as SmallInteger.
      For very special uses only - not constant across implementations"
@@ -116,464 +129,36 @@
 %}
 
     "SmallInteger maxVal"
+!
+
+minVal
+    "return the smallest Integer representable as SmallInteger.
+     For very special uses only - not constant across implementations"
+
+%{  /* NOCONTEXT */
+    RETURN ( _MKSMALLINT(_MIN_INT) );
+%}
+
+    "SmallInteger minVal"
 ! !
 
 !SmallInteger class methodsFor:'queries'!
 
-isBuiltInClass
-    "this class is known by the run-time-system"
-
-    ^ true
-!
-
 canBeSubclassed
     "return true, if its allowed to create subclasses of the receiver.
      Return nil here - since it is NOT possible for SmallInteger"
 
     ^ false
-! !
-
-!SmallInteger methodsFor:'catching messages'!
-
-basicAt:index
-    "catch indexed access - report an error
-     defined here since basicAt: in Object ommits the SmallInteger check."
-
-    self notIndexed
-!
-
-basicAt:index put:anObject
-    "catch indexed access - report an error
-     defined here since basicAt:put: in Object ommits the SmallInteger check."
-
-    self notIndexed
-!
-
-size
-    "return the number of indexed instvars - SmallIntegers have none."
-
-    ^ 0
-!
-
-basicSize
-    "return the number of indexed instvars - SmallIntegers have none.
-     Defined here since basicSize in Object ommits the SmallInteger check."
-
-    ^ 0
-! !
-
-!SmallInteger methodsFor:'copying'!
-
-shallowCopy
-    "return a shallow copy of myself
-     - reimplemented here since smallintegers are unique"
-
-    ^ self
-!
-
-simpleDeepCopy
-    "return a deep copy of myself
-     - reimplemented here since smallintegers are unique"
-
-    ^ self
-!
-
-deepCopyUsing:aDictionary
-    "return a deep copy of myself
-     - reimplemented here since smallintegers are unique"
-
-    ^ self
-!
-
-deepCopy
-    "return a deep copy of myself
-     - reimplemented here since smallintegers are unique"
-
-    ^ self
-! !
-
-!SmallInteger methodsFor:'comparing'!
-
-= aNumber
-    "return true, if the arguments value is equal to mine"
-
-%{  /* NOCONTEXT */
-
-    if (aNumber == self) {
-	RETURN ( true );
-    }
-    if (! __isNonNilObject(aNumber)) {
-	/* a smallint or nil */
-	RETURN ( false );
-    }
-
-    if (__isFloatLike(aNumber)) {
-	RETURN ( ((double)_intVal(self) == _floatVal(aNumber)) ? true : false );
-    }
-%}
-.
-    aNumber respondsToArithmetic ifFalse:[^ false].
-    ^ self retry:#= coercing:aNumber
-!
-
-~= aNumber
-    "return true, if the arguments value is not equal to mine"
-
-%{  /* NOCONTEXT */
-
-    if (aNumber == self) {
-	RETURN ( false );
-    }
-    if (! __isNonNilObject(aNumber)) {
-	/* a smallint or nil */
-	RETURN ( true );
-    }
-
-    if (__isFloatLike(aNumber)) {
-	RETURN ( ((double)_intVal(self) == _floatVal(aNumber)) ? false : true );
-    }
-%}
-.
-    aNumber respondsToArithmetic ifFalse:[^ true].
-    ^ self retry:#~= coercing:aNumber
-!
-
-< aNumber
-    "return true, if the argument is greater than the receiver"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-#ifdef POSITIVE_ADDRESSES
-	RETURN ( (_intVal(self) < _intVal(aNumber)) ? true : false );
-#else
-	/* tag bit does not change ordering */
-	RETURN ( ((INT)self < (INT)aNumber) ? true : false );
-#endif
-    }
-    if (__isFloatLike(aNumber)) {
-	RETURN ( ((double)_intVal(self) < _floatVal(aNumber)) ? true : false );
-    }
-%}
-.
-    ^ aNumber lessFromInteger:self
-    "^ self retry:#< coercing:aNumber"
-!
-
-> aNumber
-    "return true, if the argument is less than the receiver"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-#ifdef POSITIVE_ADDRESSES
-	RETURN ( (_intVal(self) > _intVal(aNumber)) ? true : false );
-#else
-	/* tag bit does not change ordering */
-	RETURN ( ((INT)self > (INT)aNumber) ? true : false );
-#endif
-    }
-    if (__isFloatLike(aNumber)) {
-	RETURN ( ((double)_intVal(self) > _floatVal(aNumber)) ? true : false );
-    }
-%}
-.
-    ^ self retry:#> coercing:aNumber
-!
-
->= aNumber
-    "return true, if the argument is less or equal"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-#ifdef POSITIVE_ADDRESSES
-	RETURN ( (_intVal(self) >= _intVal(aNumber)) ? true : false );
-#else
-	/* tag bit does not change ordering */
-	RETURN ( ((INT)self >= (INT)aNumber) ? true : false );
-#endif
-    }
-    if (__isFloatLike(aNumber)) {
-	RETURN ( ((double)_intVal(self) >= _floatVal(aNumber)) ? true : false );
-    }
-%}
-.
-    ^ self retry:#>= coercing:aNumber
 !
 
-<= aNumber
-    "return true, if the argument is greater or equal"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-#ifdef POSITIVE_ADDRESSES
-	RETURN ( (_intVal(self) <= _intVal(aNumber)) ? true : false );
-#else
-	/* tag bit does not change ordering */
-	RETURN ( ((INT)self <= (INT)aNumber) ? true : false );
-#endif
-    }
-    if (__isFloatLike(aNumber)) {
-	RETURN ( ((double)_intVal(self) <= _floatVal(aNumber)) ? true : false );
-    }
-%}
-.
-    ^ self retry:#<= coercing:aNumber
-!
-
-hash
-    "return an integer useful for hashing on value"
-
-    self >= 0 ifTrue:[^ self].
-    ^ self negated
-!
-
-identityHash
-    "return an integer useful for hashing on identity"
-
-    self >= 0 ifTrue:[^ self].
-    ^ self negated
-!
-
-min:aNumber
-    "return the receiver or the argument, whichever is smaller"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-#ifdef POSITIVE_ADDRESSES
-	if (_intVal(self) < _intVal(aNumber)) {
-#else
-	/* tag bit does not change ordering */
-	if ((INT)(self) < (INT)(aNumber)) {
-#endif
-	    RETURN ( self );
-	}
-	RETURN ( aNumber );
-    }
-    if (__isFloatLike(aNumber)) {
-	if ( (double)_intVal(self) < _floatVal(aNumber) ) {
-	    RETURN ( self );
-	}
-	RETURN ( aNumber );
-    }
-%}
-.
-    (self < aNumber) ifTrue:[^ self].
-    ^ aNumber
-!
-
-max:aNumber
-    "return the receiver or the argument, whichever is greater"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-#ifdef POSITIVE_ADDRESSES
-	if (_intVal(self) > _intVal(aNumber)) {
-#else
-	/* tag bit does not change ordering */
-	if ((INT)(self) > (INT)(aNumber)) {
-#endif
-	    RETURN ( self );
-	}
-	RETURN ( aNumber );
-    }
-    if (__isFloatLike(aNumber)) {
-	if ( (double)_intVal(self) > _floatVal(aNumber) ) {
-	    RETURN ( self );
-	}
-	RETURN ( aNumber );
-    }
-%}
-.
-    (self > aNumber) ifTrue:[^ self].
-    ^ aNumber
-! !
-
-!SmallInteger methodsFor:'testing'!
-
-negative
-    "return true, if the receiver is less than zero
-     reimplemented here for speed"
-
-%{  /* NOCONTEXT */
+isBuiltInClass
+    "this class is known by the run-time-system"
 
-#ifdef POSITIVE_ADDRESSES
-    RETURN ( (_intVal(self) < 0) ? true : false );
-#else
-    /* tag bit does not change sign */
-    RETURN ( ((INT)(self) < 0) ? true : false );
-#endif
-%}
-!
-
-positive
-    "return true, if the receiver is not negative
-     reimplemented here for speed"
-
-%{  /* NOCONTEXT */
-
-#ifdef POSITIVE_ADDRESSES
-    RETURN ( (_intVal(self) >= 0) ? true : false );
-#else
-    /* tag bit does not change sign */
-    RETURN ( ((INT)(self) >= 0) ? true : false );
-#endif
-%}
-!
-
-strictlyPositive
-    "return true, if the receiver is greater than zero
-     reimplemented here for speed"
-
-%{  /* NOCONTEXT */
-
-#ifdef POSITIVE_ADDRESSES
-    RETURN ( (_intVal(self) > 0) ? true : false );
-#else
-    /* tag bit does not change sign */
-    RETURN ( ((INT)(self) > 0) ? true : false );
-#endif
-%}
-!
-
-sign
-    "return the sign of the receiver
-     reimplemented here for speed"
-
-%{  /* NOCONTEXT */
-
-    INT val = _intVal(self);
-
-    if (val < 0) {
-	RETURN ( _MKSMALLINT(-1) ); 
-    }
-    if (val > 0) {
-	RETURN ( _MKSMALLINT(1) );
-    }
-    RETURN ( _MKSMALLINT(0) );
-%}
-!
-
-between:min and:max
-    "return true if the receiver is less than or equal to the argument max
-     and greater than or equal to the argument min.
-     - reimplemented here for speed"
-
-%{  /* NOCONTEXT */
-
-    if (__bothSmallInteger(min, max)) {
-	REGISTER INT selfVal;
-
-	selfVal = _intVal(self);
-	if (selfVal < _intVal(min)) {
-	     RETURN ( false );
-	}
-	if (selfVal > _intVal(max)) {
-	     RETURN ( false );
-	}
-	RETURN ( true );
-    }
-%}
-.
-    (self < min) ifTrue:[^ false].
-    (self > max) ifTrue:[^ false].
     ^ true
-!
-
-even
-    "return true, if the receiver is even"
-
-%{  /* NOCONTEXT */
-
-#ifdef POSITIVE_ADDRESSES
-    RETURN ( ((INT)self & 1) ? false : true );
-#else    
-    RETURN ( ((INT)self & ((INT)_MKSMALLINT(1) & ~TAG_INT)) ? false : true );
-#endif
-%}
-!
-
-odd
-    "return true, if the receiver is odd"
-
-%{  /* NOCONTEXT */
-
-#ifdef POSITIVE_ADDRESSES
-    RETURN ( ((INT)self & 1) ? true : false );
-#else    
-    RETURN ( ((INT)self & ((INT)_MKSMALLINT(1) & ~TAG_INT)) ? true : false );
-#endif
-%}
 ! !
 
 !SmallInteger methodsFor:'arithmetic'!
 
-+ aNumber
-    "return the sum of the receivers value and the arguments value"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-#ifdef _ADD_IO_IO
-	RETURN ( _ADD_IO_IO(self, aNumber) );
-#else
-	REGISTER INT sum;
-	extern OBJ _MKLARGEINT();
-
-	sum =  _intVal(self) + _intVal(aNumber);
-	if ((sum >= _MIN_INT) && (sum <= _MAX_INT)) {
-	    RETURN ( _MKSMALLINT(sum) );
-	}
-	RETURN ( _MKLARGEINT(sum) );
-#endif
-    }
-    if (__isFloatLike(aNumber)) {
-	OBJ newFloat;
-	double val = (double)_intVal(self) + _floatVal(aNumber);
-
-	_qMKFLOAT(newFloat, val, SENDER);
-	RETURN ( newFloat );
-    }
-%}
-.
-    ^ aNumber sumFromInteger:self
-!
-
-- aNumber
-    "return the difference of the receivers value and the arguments value"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-#ifdef _SUB_IO_IO
-	RETURN ( _SUB_IO_IO(self, aNumber) );
-#else
-	REGISTER INT diff;
-	extern OBJ _MKLARGEINT();
-
-	diff =  _intVal(self) - _intVal(aNumber);
-	if ((diff >= _MIN_INT) && (diff <= _MAX_INT)) {
-	    RETURN ( _MKSMALLINT(diff) );
-	}
-	RETURN ( _MKLARGEINT(diff) );
-#endif
-    }
-    if (__isFloatLike(aNumber)) {
-	OBJ newFloat;
-	double val = (double)_intVal(self) - _floatVal(aNumber);
-
-	_qMKFLOAT(newFloat, val, SENDER);
-	RETURN ( newFloat );
-    }
-%}
-.
-    ^ aNumber differenceFromInteger:self
-!
-
 * aNumber
     "return the product of the receivers value and the arguments value"
 
@@ -734,6 +319,68 @@
     ^ aNumber productFromInteger:self
 !
 
++ aNumber
+    "return the sum of the receivers value and the arguments value"
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+#ifdef _ADD_IO_IO
+	RETURN ( _ADD_IO_IO(self, aNumber) );
+#else
+	REGISTER INT sum;
+	extern OBJ _MKLARGEINT();
+
+	sum =  _intVal(self) + _intVal(aNumber);
+	if ((sum >= _MIN_INT) && (sum <= _MAX_INT)) {
+	    RETURN ( _MKSMALLINT(sum) );
+	}
+	RETURN ( _MKLARGEINT(sum) );
+#endif
+    }
+    if (__isFloatLike(aNumber)) {
+	OBJ newFloat;
+	double val = (double)_intVal(self) + _floatVal(aNumber);
+
+	_qMKFLOAT(newFloat, val, SENDER);
+	RETURN ( newFloat );
+    }
+%}
+.
+    ^ aNumber sumFromInteger:self
+!
+
+- aNumber
+    "return the difference of the receivers value and the arguments value"
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+#ifdef _SUB_IO_IO
+	RETURN ( _SUB_IO_IO(self, aNumber) );
+#else
+	REGISTER INT diff;
+	extern OBJ _MKLARGEINT();
+
+	diff =  _intVal(self) - _intVal(aNumber);
+	if ((diff >= _MIN_INT) && (diff <= _MAX_INT)) {
+	    RETURN ( _MKSMALLINT(diff) );
+	}
+	RETURN ( _MKLARGEINT(diff) );
+#endif
+    }
+    if (__isFloatLike(aNumber)) {
+	OBJ newFloat;
+	double val = (double)_intVal(self) - _floatVal(aNumber);
+
+	_qMKFLOAT(newFloat, val, SENDER);
+	RETURN ( newFloat );
+    }
+%}
+.
+    ^ aNumber differenceFromInteger:self
+!
+
 / aNumber
     "return the quotient of the receivers value and the arguments value"
 
@@ -883,91 +530,38 @@
     ^ (LargeInteger value:(SmallInteger maxVal)) + 1
 ! !
 
-!SmallInteger methodsFor:'modulu arithmetic'!
+!SmallInteger methodsFor:'binary storage'!
 
-times:aNumber
-    "return the product of the receiver and the argument, as SmallInteger.
-     The argument must be another SmallInteger.
-     If the result overflows the smallInteger range, the value modulu the 
-     smallInteger range is returned (i.e. the low bits of the product).
-     This is of course not always correct, but some code does a modulu anyway
-     and can therefore speed things up by not going through LargeIntegers."
+hasSpecialBinaryRepresentation
+    "return true, if the receiver has a special binary representation"
 
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-	RETURN ( _MKSMALLINT((_intVal(self) * _intVal(aNumber)) & 0x7FFFFFFF) );
-    }
-%}
-.
-    self primitiveFailed
+    ^ true
 !
 
-plus:aNumber
-    "return the sum of the receiver and the argument, as SmallInteger.
-     The argument must be another SmallInteger.
-     If the result overflows the smallInteger range, the value modulu the 
-     smallInteger range is returned (i.e. the low bits of the sum).
-     This is of course not always correct, but some code does a modulu anyway
-     and can therefore speed things up by not going through LargeIntegers."
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-	RETURN ( _MKSMALLINT((_intVal(self) + _intVal(aNumber)) & 0x7FFFFFFF) );
-    }
-%}
-.
-    self primitiveFailed
-! 
+storeBinaryOn: stream manager: manager
+    "append a binary representation onto stream.
+     Redefined since SmallIntegers are stored as their value with the 32nd bit 
+     set as a tag.
+     To make the binary file a bit more compact, zeros and single byte ints
+     are stored with a more compact representation (using special type-codes)."
 
-subtract:aNumber
-    "return the difference of the receiver and the argument, as SmallInteger.
-     The argument must be another SmallInteger.
-     If the result overflows the smallInteger range, the value modulu the 
-     smallInteger range is returned (i.e. the low bits of the sum).
-     This is of course not always correct, but some code does a modulu anyway
-     and can therefore speed things up by not going through LargeIntegers."
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(aNumber)) {
-	RETURN ( _MKSMALLINT((_intVal(self) - _intVal(aNumber)) & 0x7FFFFFFF) );
-    }
-%}
-.
-    self primitiveFailed
-! !
-
-!SmallInteger class methodsFor:'bit mask constants'!
-
-bitMaskFor:index
-    "return a bitmask for the index's bit (index starts at 1)"
-
-    (index between:1 and:SmallInteger maxBits) ifFalse:[
-	^ self error:'index out of bounds'
+    self == 0 ifTrue:[
+	stream nextPut: manager codeForZero.
+	^ self
     ].
-    ^ 1 bitShift:(index - 1)
+    (self between:0 and:255) ifTrue:[
+	stream nextPut: manager codeForByteInteger.
+	stream nextPut: self.
+	^ self
+    ].
+    stream nextPut: (((self bitShift: -24) bitAnd: 16rFF) bitOr: 16r80).
+    stream nextPut: ((self bitShift: -16) bitAnd: 16rFF).
+    stream nextPut: ((self bitShift: -8) bitAnd: 16rFF).
+    stream nextPut: (self bitAnd: 16rFF)
 ! !
 
 !SmallInteger methodsFor:'bit operators'!
 
-bitAt:index
-    "return the value of the index's bit (index starts at 1).
-     Notice: the result of bitAt: on negative receivers is not 
-	     defined in the language standard (since the implementation
-	     is free to choose any internal representation for integers)"
-
-    |mask|
-
-    (index between:1 and:SmallInteger maxBits) ifFalse:[
-	^ self error:'index out of bounds'
-    ].
-    mask := 1 bitShift:(index - 1).
-    ((self bitAnd:mask) == 0) ifTrue:[^ 0].
-    ^ 1
-!
-
 allMask:anInteger
     "return true if all 1-bits in anInteger are also 1 in the receiver"
 
@@ -988,79 +582,62 @@
     "2r00001111 anyMask:2r11110000"
 !
 
-noMask:anInteger
-    "return true if no 1-bit in anInteger is 1 in the receiver"
-
-    ^ (self bitAnd:anInteger) == 0
-
-    "2r00001111 noMask:2r00000001"
-    "2r00001111 noMask:2r11110000"
-!
-
-highBit
-    "return the bitIndex of the highest bit set. The returned bitIndex
-     starts at 1 for the least significant bit. Returns -1 if no bit is set."
+bitAnd:anInteger
+    "return the bitwise-and of the receiver and the argument, anInteger"
 
 %{  /* NOCONTEXT */
 
-    INT mask, index, bits;
-
-    bits = _intVal(self);
-    if (bits == 0) {
-	RETURN ( _MKSMALLINT(-1) );
+    /* anding the tags doesn't change it */
+    if (__isSmallInteger(anInteger)) {
+	RETURN ( ((OBJ) ((INT)self & (INT)anInteger)) );
     }
-#ifdef alpha
-    mask = 0x2000000000000000;
-    index = 62;
-#else
-    mask = 0x20000000;
-    index = 30;
-#endif
-    while (index) {
-	if (bits & mask) break;
-	mask = mask >> 1;
-	index--;
-    }
-    RETURN ( _MKSMALLINT(index) );
 %}
-    "2r000100 highBit"
-    "2r010100 highBit"
-    "2r000001 highBit"
-    "0 highBit"
-    "SmallInteger maxVal highBit"
+.
+    ^ self retry:#bitAnd coercing:anInteger
+
+    "(2r001010100 bitAnd:2r00001111) radixPrintStringRadix:2"
 !
 
-lowBit
-    "return the bitIndex of the lowest bit set. The returned bitIndex
-     starts at 1 for the least significant bit. Returns -1 if no bit is set."
+bitAt:index
+    "return the value of the index's bit (index starts at 1).
+     Notice: the result of bitAt: on negative receivers is not 
+	     defined in the language standard (since the implementation
+	     is free to choose any internal representation for integers)"
+
+    |mask|
+
+    (index between:1 and:SmallInteger maxBits) ifFalse:[
+	^ self error:'index out of bounds'
+    ].
+    mask := 1 bitShift:(index - 1).
+    ((self bitAnd:mask) == 0) ifTrue:[^ 0].
+    ^ 1
+!
+
+bitInvert
+    "return the value of the receiver with all bits inverted"
 
 %{  /* NOCONTEXT */
 
-    INT mask, index, bits;
+    /* invert anything except tag bits */
+    RETURN ( ((OBJ) ((INT)self ^ ~TAG_MASK)) );
+%}
+!
 
-    bits = _intVal(self);
-    if (bits == 0) {
-	RETURN ( _MKSMALLINT(-1) );
+bitOr:anInteger
+    "return the bitwise-or of the receiver and the argument, anInteger"
+
+%{  /* NOCONTEXT */
+
+    /* oring the tags doesn't change it */
+    if (__isSmallInteger(anInteger)) {
+	RETURN ( ((OBJ) ((INT)self | (INT)anInteger)) );
     }
-    mask = 1;
-    index = 1;
-#ifdef alpha
-    while (index != 63) {
-#else
-    while (index != 31) {
-#endif
-	if (bits & mask) {
-	    RETURN ( _MKSMALLINT(index) );
-	}
-	mask = mask << 1;
-	index++;
-    }
-    RETURN ( _MKSMALLINT(-1) );
 %}
-    "2r000100 lowBit"
-    "2r010010 lowBit"
-    "2r100001 lowBit"
-    "0 lowBit"
+.
+    ^ self retry:#bitOr coercing:anInteger
+
+    "(2r000000100 bitOr:2r00000011) radixPrintStringRadix:2"
 !
 
 bitShift:shiftCount
@@ -1141,36 +718,18 @@
     ^ self bitShift:(shiftCount coerce:1)
 !
 
-bitOr:anInteger
-    "return the bitwise-or of the receiver and the argument, anInteger"
+bitTest:aMask
+    "return true, if any bit from aMask is set in the receiver"
 
 %{  /* NOCONTEXT */
 
-    /* oring the tags doesn't change it */
-    if (__isSmallInteger(anInteger)) {
-	RETURN ( ((OBJ) ((INT)self | (INT)anInteger)) );
+    /* and all bits except tag */
+    if (__isSmallInteger(aMask)) {
+	RETURN ( ((INT)self & ((INT)aMask & ~TAG_MASK)) ? true : false );
     }
 %}
 .
-    ^ self retry:#bitOr coercing:anInteger
-
-    "(2r000000100 bitOr:2r00000011) radixPrintStringRadix:2"
-!
-
-bitAnd:anInteger
-    "return the bitwise-and of the receiver and the argument, anInteger"
-
-%{  /* NOCONTEXT */
-
-    /* anding the tags doesn't change it */
-    if (__isSmallInteger(anInteger)) {
-	RETURN ( ((OBJ) ((INT)self & (INT)anInteger)) );
-    }
-%}
-.
-    ^ self retry:#bitAnd coercing:anInteger
-
-    "(2r001010100 bitAnd:2r00001111) radixPrintStringRadix:2"
+    ^ self retry:#bitTest coercing:aMask
 !
 
 bitXor:anInteger
@@ -1187,38 +746,83 @@
     ^ self retry:#bitXor coercing:anInteger
 !
 
-bitInvert
-    "return the value of the receiver with all bits inverted"
-
-%{  /* NOCONTEXT */
-
-    /* invert anything except tag bits */
-    RETURN ( ((OBJ) ((INT)self ^ ~TAG_MASK)) );
-%}
-!
-
-bitTest:aMask
-    "return true, if any bit from aMask is set in the receiver"
+highBit
+    "return the bitIndex of the highest bit set. The returned bitIndex
+     starts at 1 for the least significant bit. Returns -1 if no bit is set."
 
 %{  /* NOCONTEXT */
 
-    /* and all bits except tag */
-    if (__isSmallInteger(aMask)) {
-	RETURN ( ((INT)self & ((INT)aMask & ~TAG_MASK)) ? true : false );
+    INT mask, index, bits;
+
+    bits = _intVal(self);
+    if (bits == 0) {
+	RETURN ( _MKSMALLINT(-1) );
+    }
+#ifdef alpha
+    mask = 0x2000000000000000;
+    index = 62;
+#else
+    mask = 0x20000000;
+    index = 30;
+#endif
+    while (index) {
+	if (bits & mask) break;
+	mask = mask >> 1;
+	index--;
     }
+    RETURN ( _MKSMALLINT(index) );
 %}
-.
-    ^ self retry:#bitTest coercing:aMask
+    "2r000100 highBit"
+    "2r010100 highBit"
+    "2r000001 highBit"
+    "0 highBit"
+    "SmallInteger maxVal highBit"
+!
+
+lowBit
+    "return the bitIndex of the lowest bit set. The returned bitIndex
+     starts at 1 for the least significant bit. Returns -1 if no bit is set."
+
+%{  /* NOCONTEXT */
+
+    INT mask, index, bits;
+
+    bits = _intVal(self);
+    if (bits == 0) {
+	RETURN ( _MKSMALLINT(-1) );
+    }
+    mask = 1;
+    index = 1;
+#ifdef alpha
+    while (index != 63) {
+#else
+    while (index != 31) {
+#endif
+	if (bits & mask) {
+	    RETURN ( _MKSMALLINT(index) );
+	}
+	mask = mask << 1;
+	index++;
+    }
+    RETURN ( _MKSMALLINT(-1) );
+%}
+    "2r000100 lowBit"
+    "2r010010 lowBit"
+    "2r100001 lowBit"
+    "0 lowBit"
+!
+
+noMask:anInteger
+    "return true if no 1-bit in anInteger is 1 in the receiver"
+
+    ^ (self bitAnd:anInteger) == 0
+
+    "2r00001111 noMask:2r00000001"
+    "2r00001111 noMask:2r11110000"
 ! !
 
 !SmallInteger methodsFor:'byte access'!
 
-digitLength
-    "return the number bytes used by this Integer"
-
-    ^ self abs highBit - 1 // 8 + 1
-!
-
 digitAt:index
     "return 8 bits of value, starting at byte index"
 
@@ -1282,83 +886,49 @@
      (16r12345678 digitAt:0) printStringRadix:16
      (16r12345678 digitAt:-10) printStringRadix:16
     "
+!
+
+digitLength
+    "return the number bytes used by this Integer"
+
+    ^ self abs highBit - 1 // 8 + 1
 ! !
 
-!SmallInteger methodsFor:'misc math'!
-
-gcd:anInteger
-    "return the greatest common divisor (Euclid's algorithm).
-     This has been redefined here for more speed since due to the
-     use of gcd in Fraction code, it has become time-critical for
-     some code. (thanx to MessageTally)"
-
-%{  /* NOCONTEXT */
-
-    if (__isSmallInteger(anInteger)) {
-	INT orgArg, ttt, selfInt, temp;
+!SmallInteger methodsFor:'catching messages'!
 
-	ttt = orgArg = _intVal(anInteger);
-	if (ttt) {
-	    selfInt = _intVal(self);
-	    while (ttt != 0) {
-		temp = selfInt % ttt;
-		selfInt = ttt;
-		ttt = temp;
-	    }
-	    /*
-	     * since its not defined in what the sign of
-	     * a modulu result is when the arg is negative,
-	     * change it explicitely here ...
-	     */
-	    if (orgArg < 0) {
-		/* result should be negative */
-		if (selfInt > 0) selfInt = -selfInt;
-	    } else {
-		/* result should be positive */
-		if (selfInt < 0) selfInt = -selfInt;
-	    }
-	    RETURN ( _MKSMALLINT(selfInt) );
-	}
-    }
-%}
-.
-    ^ super gcd:anInteger
+basicAt:index
+    "catch indexed access - report an error
+     defined here since basicAt: in Object ommits the SmallInteger check."
+
+    self notIndexed
 !
 
-intlog10
-    "return the truncation of log10 of the receiver -
-     stupid implementation; used to find out the number of digits needed
-     to print a number/and for conversion to a LargeInteger.
-     Implemented that way, to allow for tiny systems without a Float class
-     (i.e. without log)."
+basicAt:index put:anObject
+    "catch indexed access - report an error
+     defined here since basicAt:put: in Object ommits the SmallInteger check."
+
+    self notIndexed
+!
 
-    self <= 0 ifTrue:[
-	self error:'logarithm of negative integer'
-    ].
-    self < 10 ifTrue:[^ 1].
-    self < 100 ifTrue:[^ 2].
-    self < 1000 ifTrue:[^ 3].
-    self < 10000 ifTrue:[^ 4].
-    self < 100000 ifTrue:[^ 5].
-    self < 1000000 ifTrue:[^ 6].
-    self < 10000000 ifTrue:[^ 7].
-    self < 100000000 ifTrue:[^ 8].
-    self < 1000000000 ifTrue:[^ 9].
-    ^ 10
+basicSize
+    "return the number of indexed instvars - SmallIntegers have none.
+     Defined here since basicSize in Object ommits the SmallInteger check."
+
+    ^ 0
+!
+
+size
+    "return the number of indexed instvars - SmallIntegers have none."
+
+    ^ 0
 ! !
 
 !SmallInteger methodsFor:'coercing and converting'!
 
-coerce:aNumber
-    "return aNumber converted into receivers type"
+asCharacter
+    "Return a character with the receiver as ascii value"
 
-    ^ aNumber asInteger
-!
-
-generality
-    "return the generality value - see ArithmeticValue>>retry:coercing:"
-
-    ^ 20
+    ^ Character value:self
 !
 
 asFloat
@@ -1380,10 +950,247 @@
     ^ LargeInteger value:self
 !
 
-asCharacter
-    "Return a character with the receiver as ascii value"
+coerce:aNumber
+    "return aNumber converted into receivers type"
+
+    ^ aNumber asInteger
+!
+
+generality
+    "return the generality value - see ArithmeticValue>>retry:coercing:"
+
+    ^ 20
+! !
+
+!SmallInteger methodsFor:'comparing'!
+
+< aNumber
+    "return true, if the argument is greater than the receiver"
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+#ifdef POSITIVE_ADDRESSES
+	RETURN ( (_intVal(self) < _intVal(aNumber)) ? true : false );
+#else
+	/* tag bit does not change ordering */
+	RETURN ( ((INT)self < (INT)aNumber) ? true : false );
+#endif
+    }
+    if (__isFloatLike(aNumber)) {
+	RETURN ( ((double)_intVal(self) < _floatVal(aNumber)) ? true : false );
+    }
+%}
+.
+    ^ aNumber lessFromInteger:self
+    "^ self retry:#< coercing:aNumber"
+!
+
+<= aNumber
+    "return true, if the argument is greater or equal"
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+#ifdef POSITIVE_ADDRESSES
+	RETURN ( (_intVal(self) <= _intVal(aNumber)) ? true : false );
+#else
+	/* tag bit does not change ordering */
+	RETURN ( ((INT)self <= (INT)aNumber) ? true : false );
+#endif
+    }
+    if (__isFloatLike(aNumber)) {
+	RETURN ( ((double)_intVal(self) <= _floatVal(aNumber)) ? true : false );
+    }
+%}
+.
+    ^ self retry:#<= coercing:aNumber
+!
+
+= aNumber
+    "return true, if the arguments value is equal to mine"
+
+%{  /* NOCONTEXT */
+
+    if (aNumber == self) {
+	RETURN ( true );
+    }
+    if (! __isNonNilObject(aNumber)) {
+	/* a smallint or nil */
+	RETURN ( false );
+    }
+
+    if (__isFloatLike(aNumber)) {
+	RETURN ( ((double)_intVal(self) == _floatVal(aNumber)) ? true : false );
+    }
+%}
+.
+    aNumber respondsToArithmetic ifFalse:[^ false].
+    ^ self retry:#= coercing:aNumber
+!
+
+> aNumber
+    "return true, if the argument is less than the receiver"
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+#ifdef POSITIVE_ADDRESSES
+	RETURN ( (_intVal(self) > _intVal(aNumber)) ? true : false );
+#else
+	/* tag bit does not change ordering */
+	RETURN ( ((INT)self > (INT)aNumber) ? true : false );
+#endif
+    }
+    if (__isFloatLike(aNumber)) {
+	RETURN ( ((double)_intVal(self) > _floatVal(aNumber)) ? true : false );
+    }
+%}
+.
+    ^ self retry:#> coercing:aNumber
+!
+
+>= aNumber
+    "return true, if the argument is less or equal"
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+#ifdef POSITIVE_ADDRESSES
+	RETURN ( (_intVal(self) >= _intVal(aNumber)) ? true : false );
+#else
+	/* tag bit does not change ordering */
+	RETURN ( ((INT)self >= (INT)aNumber) ? true : false );
+#endif
+    }
+    if (__isFloatLike(aNumber)) {
+	RETURN ( ((double)_intVal(self) >= _floatVal(aNumber)) ? true : false );
+    }
+%}
+.
+    ^ self retry:#>= coercing:aNumber
+!
 
-    ^ Character value:self
+hash
+    "return an integer useful for hashing on value"
+
+    self >= 0 ifTrue:[^ self].
+    ^ self negated
+!
+
+identityHash
+    "return an integer useful for hashing on identity"
+
+    self >= 0 ifTrue:[^ self].
+    ^ self negated
+!
+
+max:aNumber
+    "return the receiver or the argument, whichever is greater"
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+#ifdef POSITIVE_ADDRESSES
+	if (_intVal(self) > _intVal(aNumber)) {
+#else
+	/* tag bit does not change ordering */
+	if ((INT)(self) > (INT)(aNumber)) {
+#endif
+	    RETURN ( self );
+	}
+	RETURN ( aNumber );
+    }
+    if (__isFloatLike(aNumber)) {
+	if ( (double)_intVal(self) > _floatVal(aNumber) ) {
+	    RETURN ( self );
+	}
+	RETURN ( aNumber );
+    }
+%}
+.
+    (self > aNumber) ifTrue:[^ self].
+    ^ aNumber
+!
+
+min:aNumber
+    "return the receiver or the argument, whichever is smaller"
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+#ifdef POSITIVE_ADDRESSES
+	if (_intVal(self) < _intVal(aNumber)) {
+#else
+	/* tag bit does not change ordering */
+	if ((INT)(self) < (INT)(aNumber)) {
+#endif
+	    RETURN ( self );
+	}
+	RETURN ( aNumber );
+    }
+    if (__isFloatLike(aNumber)) {
+	if ( (double)_intVal(self) < _floatVal(aNumber) ) {
+	    RETURN ( self );
+	}
+	RETURN ( aNumber );
+    }
+%}
+.
+    (self < aNumber) ifTrue:[^ self].
+    ^ aNumber
+!
+
+~= aNumber
+    "return true, if the arguments value is not equal to mine"
+
+%{  /* NOCONTEXT */
+
+    if (aNumber == self) {
+	RETURN ( false );
+    }
+    if (! __isNonNilObject(aNumber)) {
+	/* a smallint or nil */
+	RETURN ( true );
+    }
+
+    if (__isFloatLike(aNumber)) {
+	RETURN ( ((double)_intVal(self) == _floatVal(aNumber)) ? false : true );
+    }
+%}
+.
+    aNumber respondsToArithmetic ifFalse:[^ true].
+    ^ self retry:#~= coercing:aNumber
+! !
+
+!SmallInteger methodsFor:'copying'!
+
+deepCopy
+    "return a deep copy of myself
+     - reimplemented here since smallintegers are unique"
+
+    ^ self
+!
+
+deepCopyUsing:aDictionary
+    "return a deep copy of myself
+     - reimplemented here since smallintegers are unique"
+
+    ^ self
+!
+
+shallowCopy
+    "return a shallow copy of myself
+     - reimplemented here since smallintegers are unique"
+
+    ^ self
+!
+
+simpleDeepCopy
+    "return a deep copy of myself
+     - reimplemented here since smallintegers are unique"
+
+    ^ self
 ! !
 
 !SmallInteger methodsFor:'iteration'!
@@ -1525,6 +1332,119 @@
 "/    ]
 !
 
+to:stop by:incr do:aBlock
+    "reimplemented as primitive for speed"
+
+    |home|
+%{
+    REGISTER INT tmp, step;
+    REGISTER INT final;
+    REGISTER OBJFUNC code;
+    extern OBJ Block;
+    static struct inlineCache blockVal = __ILC1(0);
+    REGISTER OBJ rHome;
+
+    if (__bothSmallInteger(incr, stop)) {
+	tmp = _intVal(self);
+	final = _intVal(stop);
+	step = _intVal(incr);
+	if (__isBlockLike(aBlock)
+	 && ((code = _BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
+	 && (_BlockInstPtr(aBlock)->b_nargs == _MKSMALLINT(1))) {
+#ifdef NEW_BLOCK_CALL
+	    if (step < 0) {
+		while (tmp >= final) {
+		    if (InterruptPending != nil) interrupt(CONARG);
+		    (*code)(aBlock, CON_COMMA _MKSMALLINT(tmp));
+		    tmp += step;
+		}
+	    } else {
+		while (tmp <= final) {
+		    if (InterruptPending != nil) interrupt(CONARG);
+		    (*code)(aBlock, CON_COMMA _MKSMALLINT(tmp));
+		    tmp += step;
+		}
+	    }
+#else
+	    /*
+	     * arg is a compiled block - 
+	     * directly call it without going through "Block-value"
+	     */
+	    home = _BlockInstPtr(aBlock)->b_home;
+	    rHome = home;
+	    if (step < 0) {
+		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
+		    /*
+		     * home is on stack - will not move
+		     */
+		    while (tmp >= final) {
+			if (InterruptPending != nil) interrupt(CONARG);
+			(*code)(rHome, CON_COMMA _MKSMALLINT(tmp));
+			tmp += step;
+		    }
+		} else {
+		    while (tmp >= final) {
+			if (InterruptPending != nil) interrupt(CONARG);
+			(*code)(home, CON_COMMA _MKSMALLINT(tmp));
+			tmp += step;
+		    }
+		}
+	    } else {
+		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
+		    /*
+		     * home is on stack - will not move
+		     */
+		    while (tmp <= final) {
+			if (InterruptPending != nil) interrupt(CONARG);
+			(*code)(rHome, CON_COMMA _MKSMALLINT(tmp));
+			tmp += step;
+		    }
+		} else {
+		    while (tmp <= final) {
+			if (InterruptPending != nil) interrupt(CONARG);
+			(*code)(home, CON_COMMA _MKSMALLINT(tmp));
+			tmp += step;
+		    }
+		}
+	    }
+#endif
+	} else {
+	    /*
+	     * arg is something else - call it with value"
+	     */
+	    if (step < 0) {
+		while (tmp >= final) {
+		    if (InterruptPending != nil) interrupt(CONARG);
+
+		    (*blockVal.ilc_func)(aBlock, 
+					 @symbol(value:), 
+					 CON_COMMA nil, &blockVal,
+					 _MKSMALLINT(tmp));
+		    tmp += step;
+		}
+	    } else {
+		while (tmp <= final) {
+		    if (InterruptPending != nil) interrupt(CONARG);
+
+		    (*blockVal.ilc_func)(aBlock, 
+					 @symbol(value:), 
+					 CON_COMMA nil, &blockVal,
+					 _MKSMALLINT(tmp));
+		    tmp += step;
+		}
+	    }
+	}
+	RETURN ( self );
+    }
+%}
+.
+    ^ super to:stop by:incr do:aBlock
+
+    "
+     1 to:10 by:3 do:[:i | i printNewline]
+    "
+!
+
 to:stop do:aBlock
     "evaluate aBlock for every integer between (and including) the receiver
      and the argument, stop.
@@ -1668,166 +1588,125 @@
     "
      1 to:10 do:[:i | i printNewline]
     "
-!
+! !
 
-to:stop by:incr do:aBlock
-    "reimplemented as primitive for speed"
+!SmallInteger methodsFor:'misc math'!
 
-    |home|
-%{
-    REGISTER INT tmp, step;
-    REGISTER INT final;
-    REGISTER OBJFUNC code;
-    extern OBJ Block;
-    static struct inlineCache blockVal = __ILC1(0);
-    REGISTER OBJ rHome;
+gcd:anInteger
+    "return the greatest common divisor (Euclid's algorithm).
+     This has been redefined here for more speed since due to the
+     use of gcd in Fraction code, it has become time-critical for
+     some code. (thanx to MessageTally)"
+
+%{  /* NOCONTEXT */
 
-    if (__bothSmallInteger(incr, stop)) {
-	tmp = _intVal(self);
-	final = _intVal(stop);
-	step = _intVal(incr);
-	if (__isBlockLike(aBlock)
-	 && ((code = _BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
-	 && (_BlockInstPtr(aBlock)->b_nargs == _MKSMALLINT(1))) {
-#ifdef NEW_BLOCK_CALL
-	    if (step < 0) {
-		while (tmp >= final) {
-		    if (InterruptPending != nil) interrupt(CONARG);
-		    (*code)(aBlock, CON_COMMA _MKSMALLINT(tmp));
-		    tmp += step;
-		}
-	    } else {
-		while (tmp <= final) {
-		    if (InterruptPending != nil) interrupt(CONARG);
-		    (*code)(aBlock, CON_COMMA _MKSMALLINT(tmp));
-		    tmp += step;
-		}
+    if (__isSmallInteger(anInteger)) {
+	INT orgArg, ttt, selfInt, temp;
+
+	ttt = orgArg = _intVal(anInteger);
+	if (ttt) {
+	    selfInt = _intVal(self);
+	    while (ttt != 0) {
+		temp = selfInt % ttt;
+		selfInt = ttt;
+		ttt = temp;
 	    }
-#else
 	    /*
-	     * arg is a compiled block - 
-	     * directly call it without going through "Block-value"
+	     * since its not defined in what the sign of
+	     * a modulu result is when the arg is negative,
+	     * change it explicitely here ...
 	     */
-	    home = _BlockInstPtr(aBlock)->b_home;
-	    rHome = home;
-	    if (step < 0) {
-		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
-		    /*
-		     * home is on stack - will not move
-		     */
-		    while (tmp >= final) {
-			if (InterruptPending != nil) interrupt(CONARG);
-			(*code)(rHome, CON_COMMA _MKSMALLINT(tmp));
-			tmp += step;
-		    }
-		} else {
-		    while (tmp >= final) {
-			if (InterruptPending != nil) interrupt(CONARG);
-			(*code)(home, CON_COMMA _MKSMALLINT(tmp));
-			tmp += step;
-		    }
-		}
+	    if (orgArg < 0) {
+		/* result should be negative */
+		if (selfInt > 0) selfInt = -selfInt;
 	    } else {
-		if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
-		    /*
-		     * home is on stack - will not move
-		     */
-		    while (tmp <= final) {
-			if (InterruptPending != nil) interrupt(CONARG);
-			(*code)(rHome, CON_COMMA _MKSMALLINT(tmp));
-			tmp += step;
-		    }
-		} else {
-		    while (tmp <= final) {
-			if (InterruptPending != nil) interrupt(CONARG);
-			(*code)(home, CON_COMMA _MKSMALLINT(tmp));
-			tmp += step;
-		    }
-		}
+		/* result should be positive */
+		if (selfInt < 0) selfInt = -selfInt;
 	    }
-#endif
-	} else {
-	    /*
-	     * arg is something else - call it with value"
-	     */
-	    if (step < 0) {
-		while (tmp >= final) {
-		    if (InterruptPending != nil) interrupt(CONARG);
-
-		    (*blockVal.ilc_func)(aBlock, 
-					 @symbol(value:), 
-					 CON_COMMA nil, &blockVal,
-					 _MKSMALLINT(tmp));
-		    tmp += step;
-		}
-	    } else {
-		while (tmp <= final) {
-		    if (InterruptPending != nil) interrupt(CONARG);
-
-		    (*blockVal.ilc_func)(aBlock, 
-					 @symbol(value:), 
-					 CON_COMMA nil, &blockVal,
-					 _MKSMALLINT(tmp));
-		    tmp += step;
-		}
-	    }
+	    RETURN ( _MKSMALLINT(selfInt) );
 	}
-	RETURN ( self );
     }
 %}
 .
-    ^ super to:stop by:incr do:aBlock
+    ^ super gcd:anInteger
+!
 
-    "
-     1 to:10 by:3 do:[:i | i printNewline]
-    "
-! !
-
-!SmallInteger class methodsFor:'binary storage'!
+intlog10
+    "return the truncation of log10 of the receiver -
+     stupid implementation; used to find out the number of digits needed
+     to print a number/and for conversion to a LargeInteger.
+     Implemented that way, to allow for tiny systems without a Float class
+     (i.e. without log)."
 
-binaryDefinitionFrom: stream manager: manager
-    "read the binary representation as stored in storeBinaryOn:"
-
-    | value |
-
-    value := stream next bitAnd: 16r7F.
-    value > 16r3F ifTrue: [
-	value := value - 16r80
+    self <= 0 ifTrue:[
+	self error:'logarithm of negative integer'
     ].
-    value := (value bitShift: 8) bitOr: stream next.
-    value := (value bitShift: 8) bitOr: stream next.
-    value := (value bitShift: 8) bitOr: stream next.
-    ^ value
+    self < 10 ifTrue:[^ 1].
+    self < 100 ifTrue:[^ 2].
+    self < 1000 ifTrue:[^ 3].
+    self < 10000 ifTrue:[^ 4].
+    self < 100000 ifTrue:[^ 5].
+    self < 1000000 ifTrue:[^ 6].
+    self < 10000000 ifTrue:[^ 7].
+    self < 100000000 ifTrue:[^ 8].
+    self < 1000000000 ifTrue:[^ 9].
+    ^ 10
 ! !
 
-!SmallInteger methodsFor:'binary storage'!
+!SmallInteger methodsFor:'modulu arithmetic'!
 
-hasSpecialBinaryRepresentation
-    "return true, if the receiver has a special binary representation"
+plus:aNumber
+    "return the sum of the receiver and the argument, as SmallInteger.
+     The argument must be another SmallInteger.
+     If the result overflows the smallInteger range, the value modulu the 
+     smallInteger range is returned (i.e. the low bits of the sum).
+     This is of course not always correct, but some code does a modulu anyway
+     and can therefore speed things up by not going through LargeIntegers."
 
-    ^ true
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+	RETURN ( _MKSMALLINT((_intVal(self) + _intVal(aNumber)) & 0x7FFFFFFF) );
+    }
+%}
+.
+    self primitiveFailed
 !
 
-storeBinaryOn: stream manager: manager
-    "append a binary representation onto stream.
-     Redefined since SmallIntegers are stored as their value with the 32nd bit 
-     set as a tag.
-     To make the binary file a bit more compact, zeros and single byte ints
-     are stored with a more compact representation (using special type-codes)."
+subtract:aNumber
+    "return the difference of the receiver and the argument, as SmallInteger.
+     The argument must be another SmallInteger.
+     If the result overflows the smallInteger range, the value modulu the 
+     smallInteger range is returned (i.e. the low bits of the sum).
+     This is of course not always correct, but some code does a modulu anyway
+     and can therefore speed things up by not going through LargeIntegers."
+
+%{  /* NOCONTEXT */
 
-    self == 0 ifTrue:[
-	stream nextPut: manager codeForZero.
-	^ self
-    ].
-    (self between:0 and:255) ifTrue:[
-	stream nextPut: manager codeForByteInteger.
-	stream nextPut: self.
-	^ self
-    ].
-    stream nextPut: (((self bitShift: -24) bitAnd: 16rFF) bitOr: 16r80).
-    stream nextPut: ((self bitShift: -16) bitAnd: 16rFF).
-    stream nextPut: ((self bitShift: -8) bitAnd: 16rFF).
-    stream nextPut: (self bitAnd: 16rFF)
+    if (__isSmallInteger(aNumber)) {
+	RETURN ( _MKSMALLINT((_intVal(self) - _intVal(aNumber)) & 0x7FFFFFFF) );
+    }
+%}
+.
+    self primitiveFailed
+!
+
+times:aNumber
+    "return the product of the receiver and the argument, as SmallInteger.
+     The argument must be another SmallInteger.
+     If the result overflows the smallInteger range, the value modulu the 
+     smallInteger range is returned (i.e. the low bits of the product).
+     This is of course not always correct, but some code does a modulu anyway
+     and can therefore speed things up by not going through LargeIntegers."
+
+%{  /* NOCONTEXT */
+
+    if (__isSmallInteger(aNumber)) {
+	RETURN ( _MKSMALLINT((_intVal(self) * _intVal(aNumber)) & 0x7FFFFFFF) );
+    }
+%}
+.
+    self primitiveFailed
 ! !
 
 !SmallInteger methodsFor:'printing & storing'!
@@ -1838,6 +1717,13 @@
     aStream nextPutAll:(self printString)
 !
 
+printOn:aStream base:radix
+    "append my printstring in any number base to aStream.
+     The radix argument should be between 2 and 36."
+
+    aStream nextPutAll:(self printStringRadix:radix)
+!
+
 printString
     "return my printstring (base 10)"
 
@@ -1873,13 +1759,6 @@
     ^ super printString
 !
 
-printOn:aStream base:radix
-    "append my printstring in any number base to aStream.
-     The radix argument should be between 2 and 36."
-
-    aStream nextPutAll:(self printStringRadix:radix)
-!
-
 printStringRadix:radix
     "return my printstring (optimized for bases 16, 10 and 8)"
 
@@ -1979,3 +1858,126 @@
     "123 printfPrintString:'%%4x -> %4x'"
     "123 printfPrintString:'%%04x -> %04x'"
 ! !
+
+!SmallInteger methodsFor:'testing'!
+
+between:min and:max
+    "return true if the receiver is less than or equal to the argument max
+     and greater than or equal to the argument min.
+     - reimplemented here for speed"
+
+%{  /* NOCONTEXT */
+
+    if (__bothSmallInteger(min, max)) {
+	REGISTER INT selfVal;
+
+	selfVal = _intVal(self);
+	if (selfVal < _intVal(min)) {
+	     RETURN ( false );
+	}
+	if (selfVal > _intVal(max)) {
+	     RETURN ( false );
+	}
+	RETURN ( true );
+    }
+%}
+.
+    (self < min) ifTrue:[^ false].
+    (self > max) ifTrue:[^ false].
+    ^ true
+!
+
+even
+    "return true, if the receiver is even"
+
+%{  /* NOCONTEXT */
+
+#ifdef POSITIVE_ADDRESSES
+    RETURN ( ((INT)self & 1) ? false : true );
+#else    
+    RETURN ( ((INT)self & ((INT)_MKSMALLINT(1) & ~TAG_INT)) ? false : true );
+#endif
+%}
+!
+
+negative
+    "return true, if the receiver is less than zero
+     reimplemented here for speed"
+
+%{  /* NOCONTEXT */
+
+#ifdef POSITIVE_ADDRESSES
+    RETURN ( (_intVal(self) < 0) ? true : false );
+#else
+    /* tag bit does not change sign */
+    RETURN ( ((INT)(self) < 0) ? true : false );
+#endif
+%}
+!
+
+odd
+    "return true, if the receiver is odd"
+
+%{  /* NOCONTEXT */
+
+#ifdef POSITIVE_ADDRESSES
+    RETURN ( ((INT)self & 1) ? true : false );
+#else    
+    RETURN ( ((INT)self & ((INT)_MKSMALLINT(1) & ~TAG_INT)) ? true : false );
+#endif
+%}
+!
+
+positive
+    "return true, if the receiver is not negative
+     reimplemented here for speed"
+
+%{  /* NOCONTEXT */
+
+#ifdef POSITIVE_ADDRESSES
+    RETURN ( (_intVal(self) >= 0) ? true : false );
+#else
+    /* tag bit does not change sign */
+    RETURN ( ((INT)(self) >= 0) ? true : false );
+#endif
+%}
+!
+
+sign
+    "return the sign of the receiver
+     reimplemented here for speed"
+
+%{  /* NOCONTEXT */
+
+    INT val = _intVal(self);
+
+    if (val < 0) {
+	RETURN ( _MKSMALLINT(-1) ); 
+    }
+    if (val > 0) {
+	RETURN ( _MKSMALLINT(1) );
+    }
+    RETURN ( _MKSMALLINT(0) );
+%}
+!
+
+strictlyPositive
+    "return true, if the receiver is greater than zero
+     reimplemented here for speed"
+
+%{  /* NOCONTEXT */
+
+#ifdef POSITIVE_ADDRESSES
+    RETURN ( (_intVal(self) > 0) ? true : false );
+#else
+    /* tag bit does not change sign */
+    RETURN ( ((INT)(self) > 0) ? true : false );
+#endif
+%}
+! !
+
+!SmallInteger class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic/SmallInteger.st,v 1.40 1995-12-07 21:36:33 cg Exp $'
+! !