LargeInteger.st
author Claus Gittinger <cg@exept.de>
Mon, 07 Jul 2003 17:54:32 +0200
changeset 7478 2f7430bfd7ac
parent 7471 c5d4bd612d9f
child 7479 aa300239f298
permissions -rw-r--r--
tuned lowBit (req'd for gcd)

"
 COPYRIGHT (c) 1994 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

"{ Package: 'stx:libbasic' }"

Integer subclass:#LargeInteger
	instanceVariableNames:'sign digitByteArray'
	classVariableNames:''
	poolDictionaries:''
	category:'Magnitude-Numbers'
!

!LargeInteger class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    This class provides arbitrary precision integers. These are represented as:
      sign (-1/0/+1) and, if sign ~~ 0
      a ByteArray of digits with 8 bits per element; 
      least significant 8 bits at index 1 ...

    The implementation is not completely tuned for high performance
    (more key-methods should be rewritten as primitives), although the
    common operations have been pretty tuned for some architectures.

    LargeIntegers are usually not created explicitely, but result from 
    SmallInteger arithmetic (overflowing the SmallInteger range).
    Also, results of LargeInteger operations are converted to back to 
    SmallIntegers, when possible (see #compressed).

    In contrast to ST-80, there is only one class for LargeIntegers, keeping
    the sign as an instance variable (ST-80 has LargePositiveInteger and
    LargeNegativeInteger). This may change.

    [author:]
	Claus Gittinger

    [see also:]
	Number
	Float Fraction FixedPoint 
	SmallInteger
"
!

testing
"
   test largeInt multiplication & division 
   (at least, test if they have not both errors which anull each other ;-)

   |last v|

   v := last := 1.
   2 to:3000 do:[:i |
       i printCR.
       v := v * i.
       (v / i) ~= last ifTrue:[
	   self halt
       ].
       last := v.
   ]


   test addition, subtraction:

   SmallInteger maxVal                -> 1073741823
   SmallInteger maxVal + 1            -> 1073741824
   SmallInteger maxVal + 2            -> 1073741825
   (SmallInteger maxVal + 2) - 2      -> 1073741823

   SmallInteger minVal                -> -1073741824
   SmallInteger minVal - 1            -> -1073741825
   SmallInteger minVal - 2            -> -1073741826
   (SmallInteger minVal - 2) + 2      -> -1073741824

   1234567890 + 10                    -> 1234567900
   1111111111 + 1111111111            -> 2222222222
   1111111111 - 1111111111            -> 0
   1111111111 - 2222222222            -> -1111111111

   1111111111 * 2                     -> 2222222222
   1111111111 * -2                    -> -2222222222

   1111111111 * 1111111111            -> 1234567900987654321
   1234567900987654321 // 1111111111  -> 1111111111
   1234567900987654321 \\ 1111111111  -> 0
   1234567900987654322 \\ 1111111111  -> 1
   1234567900987654421 \\ 1111111111  -> 100


   addition:
   (16rFFFFFFF0 + 1          ) hexPrintString -> 'FFFFFFF1'     
   (16rFFFFFFFF + 1          ) hexPrintString -> '100000000'
   (16rFFFFFFFF + 2          ) hexPrintString -> '100000001'
   (16rFFFFFFFF + 16rFFFFFF  ) hexPrintString -> '100FFFFFE'
   (16rFFFFFFFF + 16rFFFFFFFF) hexPrintString -> '1FFFFFFFE'

   20 factorial         -> 2432902008176640000
   20 factorial + 10000 -> 2432902008176650000
   20 factorial               hexPrintString -> '21C3677C82B40000'
   (20 factorial + 16rFFFF)   hexPrintString -> '21C3677C82B4FFFF'
   (20 factorial + 16rFFFFFF) hexPrintString -> '21C3677C83B3FFFF'

   test comparison:

   -1234567890 >  -1234567890         false
   -1234567890 >= -1234567890         true
   -1234567890 <  -1234567890         false
   -1234567890 <= -1234567890         true
   -1234567890 =  -1234567890         true
   -1234567890 ~= -1234567890         false

   -1234567890 >  -1234567891         true
   -1234567890 >= -1234567891         true
   -1234567890 <  -1234567891         false
   -1234567890 <= -1234567891         false
   -1234567890 =  -1234567891         false
   -1234567890 ~= -1234567891         true

   -1234567891 >  -1234567890         false
   -1234567891 >= -1234567890         false
   -1234567891 <  -1234567890         true
   -1234567891 <= -1234567890         true
   -1234567891 =  -1234567890         false
   -1234567891 ~= -1234567890         true

    1234567890 >  -1234567890         true
    1234567890 >= -1234567890         true
    1234567890 <  -1234567890         false
    1234567890 <= -1234567890         false
    1234567890 =  -1234567890         false
    1234567890 ~= -1234567890         true

   -1234567890 >  1234567890          false
   -1234567890 >= 1234567890          false
   -1234567890 <  1234567890          true
   -1234567890 <= 1234567890          true
   -1234567890 =  1234567890          false
   -1234567890 ~= 1234567890          true

    1234567890 >  1234567890          false
    1234567890 >= 1234567890          true
    1234567890 <  1234567890          false
    1234567890 <= 1234567890          true
    1234567890 =  1234567890          true
    1234567890 ~= 1234567890          false

   -1234567890 >  -10                 false
   -1234567890 >= -10                 false
   -1234567890 <  -10                 true
   -1234567890 <= -10                 true
   -1234567890 =  -10                 false
   -1234567890 ~= -10                 true

   -1234567890 >  10                  false
   -1234567890 >= 10                  false
   -1234567890 <  10                  true
   -1234567890 <= 10                  true
   -1234567890 =  10                  false
   -1234567890 ~= 10                  true

   -10 >  -1234567890                 true
   -10 >= -1234567890                 true
   -10 <  -1234567890                 false
   -10 <= -1234567890                 false
   -10 =  -1234567890                 false
   -10 ~= -1234567890                 true

    10 >  -1234567890                 true
    10 >= -1234567890                 true
    10 <  -1234567890                 false
    10 <= -1234567890                 false
    10 =  -1234567890                 false
    10 ~= -1234567890                 true

    1234567890 >  -10                 true  
    1234567890 >= -10                 true  
    1234567890 <  -10                 false  
    1234567890 <= -10                 false  
    1234567890 =  -10                 false  
    1234567890 ~= -10                 true  

    1234567890 >  10                  true
    1234567890 >= 10                  true
    1234567890 <  10                  false
    1234567890 <= 10                  false
    1234567890 =  10                  false
    1234567890 ~= 10                  true

   -10 >   1234567890                 false
   -10 >=  1234567890                 false
   -10 <   1234567890                 true
   -10 <=  1234567890                 true
   -10 =   1234567890                 false
   -10 ~=  1234567890                 true

    10 >   1234567890                 false
    10 >=  1234567890                 false
    10 <   1234567890                 true
    10 <=  1234567890                 true
    10 =   1234567890                 false
    10 ~=  1234567890                 true
"
! !

!LargeInteger class methodsFor:'instance creation'!

digitBytes:aByteArrayOfDigits
    "create and return a new LargeInteger with digits (lsb-first)
     from the argument, aByteArray.
     Experimental interface - May change/be removed without notice."

    ^ self basicNew setDigits:aByteArrayOfDigits

    "
     LargeInteger digitBytes:#[16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF]
     (LargeInteger digitBytes:#[16r12 16r34 16r56 16r78 16r90]) hexPrintString
    "

    "Modified: / 8.5.1998 / 21:40:41 / cg"
!

digitBytes:aByteArrayOfDigits MSB:msb
    "create and return a new LargeInteger with digits (which may be in either msb/lsb order)
     from the argument, aByteArray."

    |digits|

    msb == false ifTrue:[
	digits := aByteArrayOfDigits
    ] ifFalse:[
	digits := aByteArrayOfDigits copy reverse
    ].
    ^ self basicNew setDigits:digits

    "
     (LargeInteger digitBytes:#[16r10 16r20 16r30 16r00] MSB:false) hexPrintString  
     (LargeInteger digitBytes:#[16r10 16r20 16r30 16r00] MSB:true) hexPrintString   
    "
!

new
    "catch creation message.
     LargeIntegers are only created by system code, which 
     uses basicNew and cares for correct initialization."

    self error:'LargeIntegers cannot be created with new'
!

new:numberOfDigits
    "catch creation message"

    self error:'LargeIntegers cannot be created with new'
!

value:aSmallInteger
    "create and return a new LargeInteger with value taken from
     the argument, aSmallInteger.
     Notice: 
	this should be only used internally, since such small
	largeIntegers do not normally occur in the system.
	(They are used by myself)
     May change/be removed without notice."

    ^ self basicNew value:aSmallInteger

    "LargeInteger value:3689"

    "Modified: / 8.5.1998 / 21:40:41 / cg"
! !

!LargeInteger class methodsFor:'queries'!

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

    ^ true

    "Modified: 23.4.1996 / 15:59:21 / cg"
! !

!LargeInteger methodsFor:'arithmetic'!

* aNumber
    "return the product of the receiver and the argument, aNumber"

    |otherSign numberClass|

    (sign == 0) ifTrue:[^ 0].  "cannot happen if correctly normalized"

    "
     this is the common case, multiplying with SmallInteger.
     Use a special method for this case ...
    "
    ((numberClass := aNumber class) == SmallInteger) ifTrue:[
	^ self productFromInteger:aNumber
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (numberClass == self class) ifFalse:[
	^ self retry:#* coercing:aNumber
    ].

    otherSign := aNumber sign.
    (sign == otherSign) ifTrue:[^ self absMul:aNumber].
    (otherSign == 0) ifTrue:[^ 0].
    ^ (self absMul:aNumber) sign:-1
!

+ aNumber
    "return the sum of the receiver and the argument, aNumber"

    |otherSign numberClass|

    (sign == 0) ifTrue:[^ aNumber].  "cannot happen if correctly normalized"

    "
     this is the common case, adding a SmallInteger.
     Use a special method for this case ...
    "
    ((numberClass := aNumber class) == SmallInteger) ifTrue:[
	^ self sumFromInteger:aNumber
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (numberClass == self class) ifFalse:[
	^ self retry:#+ coercing:aNumber
    ].

    otherSign := aNumber sign.
    (sign > 0) ifTrue:[
	"I am positive"
	(otherSign > 0) ifTrue:[^ self absPlus:aNumber sign:1].
	(otherSign < 0) ifTrue:[^ self absMinus:aNumber sign:1].
	^ self
    ].
    "I am negative"
    (otherSign > 0) ifTrue:[^ aNumber absMinus:self sign:1].
    (otherSign < 0) ifTrue:[^ self absPlus:aNumber sign:-1].
    ^ self

    "
     SmallInteger maxVal 
     SmallInteger maxVal + 1  
     SmallInteger maxVal + 2 
     SmallInteger minVal    
     SmallInteger minVal - 1
    "

    "Modified: / 9.1.1998 / 13:26:28 / cg"
!

- aNumber
    "return the difference of the receiver and the argument, aNumber"

    |otherSign numberClass|

    (sign == 0) ifTrue:[^ aNumber negated].     "cannot happen if correctly normalized"

    "
     this is the common case, subtracting a SmallInteger.
     Use a special method for this case ...
    "
    ((numberClass := aNumber class) == SmallInteger) ifTrue:[
	sign > 0 ifTrue:[
	    aNumber > 0 ifTrue:[
		^ self absFastMinus:aNumber sign:1
	    ].
	    ^ self absFastPlus:aNumber sign:1
	].
	aNumber > 0 ifTrue:[
	    ^ self absFastPlus:aNumber sign:-1
	].
	^ self absFastMinus:aNumber sign:-1
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (numberClass == self class) ifFalse:[
	^ self retry:#- coercing:aNumber
    ].

    otherSign := aNumber sign.
    (sign > 0) ifTrue:[
	"I am positive"
	(otherSign > 0) ifTrue:[
	    "+large - +large"
	    ^ self absMinus:aNumber sign:1
	].
	(otherSign < 0) ifTrue:[
	    "+large - -large"
	    ^ self absPlus:aNumber sign:1
	].
	"should not happen"
	^ self
    ].
    "I am negative"
    (otherSign > 0) ifTrue:[
	"-large - +large"
	^ self absPlus:aNumber sign:-1
    ].
    (otherSign < 0) ifTrue:[
	"-large - -large"
	^ self absMinus:aNumber sign:-1
    ].
    ^ self

    "
     12345678901234567890 - 0     
     12345678901234567890 - 1      
     12345678901234567890 - -1    
     -12345678901234567890 - 1     
     -12345678901234567890 - -1    

     12345678901234567890 - 12345678901234567880     
     12345678901234567890 - 12345000000000000000     
     12345678901234567890 - -87654321098765432110    
     -12345678901234567890 - 87654321098765432110    
     -12345678901234567890 - -12345678901234567880   
     -12345678901234567890 - -12345678901234567980   
    "

    "Modified: 20.10.1996 / 18:42:16 / cg"
!

/ aNumber
    "return the quotient of the receiver and the argument, aNumber"

    aNumber isInteger ifTrue:[
	^ Fraction numerator:self
		  denominator:aNumber
    ].

    "this is a q&d hack - we loose lots of precision here ..."
    ^ (self asFloat / aNumber asFloat)

    "Modified: 28.7.1997 / 19:07:55 / cg"
!

// aNumber
    "return the quotient of the receiver and the argument, aNumber.
     The result is truncated toward negative infinity and negative,
     if the operands signs differ.
     The following is always true:
	(receiver // aNumber) * aNumber + (receiver \\ aNUmber) = receiver
    "

    |cls divMod quo abs "{ Class: SmallInteger }" n|


    cls := aNumber class.

    "
     this is the common case, dividing by a SmallInteger.
     Use a special method for this case ...
    "
    (cls == SmallInteger) ifTrue:[
	abs := aNumber.
	abs := abs abs.
	(abs between:1 and:16r00ffffff) ifTrue:[
	    divMod := self absFastDivMod:abs.
	] ifFalse:[
	    n := abs asLargeInteger.
	].
    ] ifFalse:[
	"
	 if the argument is not a largeInteger, coerce
	"
	(cls == self class) ifFalse:[
	    ^ self retry:#// coercing:aNumber
	].
	n := aNumber
    ].

    divMod isNil ifTrue:[
	divMod := self absDivMod:n.
    ].
    quo := divMod at:1.
    (sign == aNumber sign) ifFalse:[
	"/ adjust for truncation if negative and there is a remainder ...
	quo := quo sign:-1.
	(divMod at:2) == 0 ifFalse:[
	    ^ quo - 1
	].
    ].
    ^ quo

    "
     (9000000000 // 4000000000)   =   (900 // 400)   ifFalse:[self halt].
     (-9000000000 // 4000000000)  =   (-900 // 400)  ifFalse:[self halt].
     (9000000000 // -4000000000)  =   (900 // -400)  ifFalse:[self halt].
     (-9000000000 // -4000000000) =   (-900 // -400) ifFalse:[self halt].

     16rfffffffff // 16r01ffffff  =   2048 ifFalse:[self halt].
     16rfffffffff // 16r00ffffff  =   4096 ifFalse:[self halt].
     16rfffffffff // 16r001fffff  =  32768 ifFalse:[self halt].

     900 quo: 400   
     -900 quo: 400                   
     900 quo: -400                   
     -900 quo: -400 

     9000000000 quo: 4000000000   
     -9000000000 quo: 4000000000  
     9000000000 quo: -4000000000  


     0 // 40000000000000000        
    "

    "Modified: / 5.11.1996 / 16:39:36 / cg"
    "Modified: / 27.4.1999 / 19:50:26 / stefan"
!

\\ aNumber
    "Answer the integer remainder m defined by division with truncation toward
     negative infinity. The remainder has the same sign as aNumber.
     m < |aNumber| AND there is an integer k with (k * aNumber + m) = self
     The following is always true:
	(receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
     Compare with #rem:"

    |abs rem negativeDivisor|

    aNumber negative ifTrue:[
	negativeDivisor := true.
	abs := aNumber negated.
    ] ifFalse:[
	negativeDivisor := false.
	abs := aNumber.
    ].

    "
     this is the common case, dividing by a SmallInteger.
     Use a special method for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
	(abs between:1 and:16r00ffffff) ifTrue:[
	    rem := (self absFastDivMod:abs) at:2.
	] ifFalse:[
	    rem := self absMod:abs asLargeInteger
	].
    ] ifFalse:[
	"
	 if the argument is not a largeInteger, coerce
	"
	(aNumber class == self class) ifFalse:[
	    ^ self retry:#\\ coercing:aNumber
	].

	rem := self absMod:abs.
    ].

    rem = 0 ifFalse:[
	negativeDivisor ifTrue:[
	    rem := rem sign:-1
	].
	(self negative ~~ negativeDivisor) ifTrue:[
	    "different sign, so remainder would have been negative.
	     rem has been rounded toward zero, this code will simulate
	     rounding to negative infinity."

	    rem := aNumber - rem.
	].
    ].
    ^ rem

    "
     (9000000000 \\ 4000000000)   = (900 \\ 400 * 10000000)  ifFalse:[self halt].
     (-9000000000 \\ 4000000000)  = (-900 \\ 400 * 10000000) ifFalse:[self halt].
     (9000000000 \\ -4000000000)  = (900 \\ -400 * 10000000) ifFalse:[self halt].
     (-9000000000 \\ -4000000000) = (-900 \\ -400 * 10000000)ifFalse:[self halt].
     (16000000000 \\ 4000000000)  = (1600 \\ 400 * 10000000) ifFalse:[self halt].
     (-16000000000 \\ 4000000000)  = (-1600 \\ 400 * 10000000) ifFalse:[self halt].
     (16000000000 \\ -4000000000)  = (1600 \\ -400 * 10000000) ifFalse:[self halt].
     (-16000000000 \\ -4000000000)  = (-1600 \\ -400 * 10000000) ifFalse:[self halt].

     9000000000 \\ 7      
     -9000000000 \\ 7     
     9000000000 \\ -7     
     -9000000000 \\ -7    

     900 rem: 400    
     -900 rem: 400  
     900 rem: -400   
     -900 rem: -400               

     9000000000 rem: 4000000000    
     -9000000000 rem: 4000000000   
     9000000000 rem: -4000000000   
     -9000000000 rem: -4000000000  
    "

    "Modified: / 5.11.1996 / 17:10:10 / cg"
    "Modified: / 27.4.1999 / 20:03:40 / stefan"
!

abs
    "return my absolute value. redefined for speed."

    sign >= 0 ifTrue:[^ self].
    ^ self negated

    "Created: / 26.10.1999 / 21:28:06 / stefan"
!

divMod:aNumber
    "return an array filled with self // aNumber and
     self \\ aNumber.
     The result is only defined for positive receiver and
     argument."

    |cls n|

    cls := aNumber class.
    (cls == SmallInteger) ifTrue:[
	"
	 this is the common case, dividing by a SmallInteger.
	 Use a special method for this case ...
	"
	(aNumber between:1 and:16r00ffffff) ifTrue:[
	    ^ self absFastDivMod:aNumber abs.
	].
	n := aNumber asLargeInteger.
    ] ifFalse:[
	(cls == self class) ifFalse:[
	    ^ super divMod:aNumber            
	].
	n := aNumber.
    ].

    ^ self absDivMod:n abs

    "
     9000000000 // 4000000000   => 2
     9000000000 \\ 4000000000   => 1000000000 
     9000000000 divMod: 4000000000   => #(2 1000000000)
    "

    "Created: / 29.10.1996 / 21:22:05 / cg"
    "Modified: / 27.4.1999 / 19:48:58 / stefan"
!

negated
    "return an integer with value negated from the receivers value."

    |newNumber sz|

    (sign == 0) ifTrue:[^ 0].

    "
     special case for SmallInteger minVal
    "
    sign == 1 ifTrue:[
	sz := digitByteArray size.
%{
	int idx;
	unsigned char *bp;

	bp = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
	idx = __intVal(sz);

	while ((idx > 1) && (bp[idx-1] == 0)) idx--;

	if (idx == sizeof(INT)) {
#if defined(alpha64)
	    if ( ((unsigned INT *)bp)[0] == 0x4000000000000000L)
#else
# if defined(__LSBFIRST)
	    if ( ((unsigned INT *)bp)[0] == 0x40000000)
# else
	    /*
	     * generic code
	     */
	    if ((bp[idx-1] == 0x40)
	     && (bp[idx-2] == 0)
	     && (bp[idx-3] == 0)
	     && (bp[idx-4] == 0)
#  ifdef alpha64
	     && (bp[idx-5] == 0)
	     && (bp[idx-6] == 0)
	     && (bp[idx-7] == 0)
	     && (bp[idx-8] == 0)
#  endif
	    ) 
# endif
#endif
	    {
		RETURN (__MKSMALLINT(_MIN_INT));
	    }
	}
%}.
"/      sz == 4 ifTrue:[
"/        (digitByteArray at:1) == 0 ifTrue:[
"/          (digitByteArray at:2) == 0 ifTrue:[
"/            (digitByteArray at:3) == 0 ifTrue:[
"/              (digitByteArray at:4) == 16r40 ifTrue:[
"/                ^ SmallInteger minVal
"/              ].
"/            ]
"/          ]
"/        ]
"/      ]
    ].
    "/ cg - can share the digits ...
    newNumber := LargeInteger digitBytes:digitByteArray.
    newNumber sign:(sign negated).
    ^ newNumber
!

quo:aNumber
    "return the quotient of the receiver and the argument, aNumber.
     The result is truncated toward zero (which is different from //, which
     truncates toward negative infinity).
     The results sign is negative if the receiver has a sign
     different from the args sign.
     The following is always true:
	(receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
    "

    |otherSign quo abs "{ Class: SmallInteger }" |

    otherSign := aNumber sign.

    "
     this is the common case, dividing by a SmallInteger.
     Use a special method for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
	abs := aNumber.
	abs := abs abs.
	(abs between:1 and:16r00ffffff) ifTrue:[
	    quo := (self absFastDivMod:abs) at:1.
	    (sign == otherSign) ifTrue:[^ quo].
	    ^ quo sign:-1
	]
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (aNumber class == self class) ifFalse:[
	^ self retry:#quo: coercing:aNumber
    ].

    sign < 0 ifTrue:[
	(sign == otherSign) ifTrue:[^ (self absDivMod:aNumber negated) at:1].
    ] ifFalse:[
	(sign == otherSign) ifTrue:[^ (self absDivMod:aNumber) at:1].
    ].
    ^ ((self absDivMod:aNumber) at:1) sign:-1

    "
     900 // 400  
     -900 // 400  
     900 // -400 
     -900 // -400  

     9000000000 // 4000000000     
     -9000000000 // 4000000000    
     9000000000 // -4000000000    
     -9000000000 // -4000000000   

     900 quo: 400    
     -900 quo: 400    
     900 quo: -400  
     -900 quo: -400  

     9000000000 quo: 4000000000   
     -9000000000 quo: 4000000000  
     9000000000 quo: -4000000000  
     -9000000000 quo: -4000000000  
    "

    "Modified: / 5.11.1996 / 14:14:17 / cg"
    "Modified: / 27.4.1999 / 20:01:22 / stefan"
!

rem:aNumber
    "return the remainder of division of the receiver by the argument, aNumber.
     The returned remainder has the same sign as the receiver.
     The following is always true:
	(receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
    "

    |rem abs "{ Class: SmallInteger }" |

    "
     this is the common case, dividing by a SmallInteger.
     Use special code for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
	abs := aNumber.
	abs := abs abs.
	(abs between:1 and:16r00ffffff) ifTrue:[
	    rem := (self absFastDivMod:abs) at:2.
	] ifFalse:[
	    rem := self absMod:abs asLargeInteger
	].
    ] ifFalse:[
	"
	 if the argument is not a largeInteger, coerce
	"
	(aNumber class == self class) ifFalse:[
	    ^ self retry:#rem coercing:aNumber
	].

	rem := self absMod:aNumber
    ].

    sign < 0 ifTrue:[
	^ rem sign:-1
    ].
    ^ rem

    "
     900 \\ 400    
     -900 \\ 400   
     900 \\ -400   
     -900 \\ -400  

     9000000000 \\ 4000000000    
     -9000000000 \\ 4000000000   
     9000000000 \\ -4000000000   
     -9000000000 \\ -4000000000  

     900 rem: 400     
     -900 rem: 400    
     900 rem: -400    
     -900 rem: -400   

     9000000000 rem: 4000000000     
     -9000000000 rem: 4000000000    
     9000000000 rem: -4000000000    
     -9000000000 rem: -4000000000   
    "

    "Modified: / 5.11.1996 / 14:02:59 / cg"
    "Modified: / 29.4.1999 / 11:26:51 / stefan"
! !

!LargeInteger methodsFor:'bit operators'!

bitAnd:anInteger
    "return the bitwise-and of the receiver and the argument, anInteger"

%{  /* NOCONTEXT */

    if (__isSmallInteger(anInteger)) {
	INT v2 = __intVal(anInteger);
	INT v1;
#if defined(__LSBFIRST) || defined(i386)
	v1 = *(INT *)(__stringVal(__INST(digitByteArray)));
#else
	unsigned char *digits = (unsigned char *)(__stringVal(__INST(digitByteArray)));

	v1 = digits[0] & 0xFF;
	v1 = v1 | ((digits[1] & 0xFF)<<8);
	v1 = v1 | ((digits[2] & 0xFF)<<16);
	v1 = v1 | ((digits[3] & 0xFF)<<24);
	if (sizeof(unsigned INT) == 8) {
	    v1 = v1 | ((digits[4] & 0xFF)<<32);
	    v1 = v1 | ((digits[5] & 0xFF)<<40);
	    v1 = v1 | ((digits[6] & 0xFF)<<48);
	    v1 = v1 | ((digits[7] & 0xFF)<<56);
	}
#endif

	RETURN ( __MKSMALLINT(v1 & v2) );
    }
%}.
    ^ super bitAnd:anInteger

    "
     (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFF) hexPrintString
     (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFF) hexPrintString  
     (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFFFF) hexPrintString   
     (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFFFFFF) hexPrintString  
     (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFFFFFFFF) hexPrintString       
     (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFFFFFFFFFF) hexPrintString     
     (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFFFFFFFFFFFF) hexPrintString   
     (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFFFFFFFFFFFFFF) hexPrintString   
    "

    "Modified: / 26.9.2001 / 17:34:03 / cg"
!

bitXor:anInteger
    "return the bitwise-or of the receiver and the argument, anInteger.
     Here, a specially tuned version for largeInteger arguments 
     (to speed up some cryptographic code)"

    |len1 len2 
     "/ n "{ Class: SmallInteger }"
     "/ result byte 
     newBytes|

    anInteger class ~~ LargeInteger ifTrue:[^ super bitXor:anInteger].

    (len1 := anInteger digitLength) > (len2 := self digitLength) ifTrue:[
	newBytes := anInteger digits copy.
	newBytes bitXorBytesFrom:1 to:len2 with:digitByteArray startingAt:1 
    ] ifFalse:[
	newBytes := digitByteArray copy.
	newBytes bitXorBytesFrom:1 to:len1 with:anInteger digits startingAt:1 
    ].
    ^ (LargeInteger digitBytes:newBytes) compressed

    "
     (16r112233445566778899 bitXor:16rFF                ) printStringRadix:16 '112233445566778866' 
     (16r112233445566778899 bitXor:16rFFFFFFFFFFFFFFFF00) printStringRadix:16 'EEDDCCBBAA99887799'
     (16r112233445566778899 bitXor:16rFF0000000000000000) printStringRadix:16 'EE2233445566778899'
     (16r112233445566778899 bitXor:16r112233445566778800) printStringRadix:16 '99' 

     |bigNum1 bigNum2|

     bigNum1 := 2 raisedToInteger:512.
     bigNum2 := 2 raisedToInteger:510.
     Time millisecondsToRun:[
	1000000 timesRepeat:[
	   bigNum1 bitXor:bigNum2.
	]
     ]      
    "
!

lowBit
    "return the bitIndex of the lowest bit set. The returned bitIndex
     starts at 1 for the least significant bit. 
     Returns 0 if no bit is set.
     For negative numbers, the low bit of my absolute value is returned.
     Redefined here for more performance of the gcd: algorithm, which
     is used when big fractions are reduced (should we write a primitive for this ?)."

    |sz   "{ Class: SmallInteger }"
     idx0 "{ Class: SmallInteger }"
     byte|

    sz := digitByteArray size.
    idx0 := 1.

%{
#if 1
    if (__isByteArray(__INST(digitByteArray))) {
        int __sz = __intVal(sz);
        unsigned char *__bP = (unsigned char *)(__byteArrayVal(__INST(digitByteArray)));
        unsigned char *__bP0 = __bP;

        while (__sz > sizeof(INT)) {
            if ( ((INT *)__bP)[0] != 0 ) break;
            __sz -= sizeof(INT);
            __bP += sizeof(INT);
        }
        while (__sz > 0) {
            int c;

            if ( (c = *__bP) != 0 ) {
                int bitIdx = (__bP - __bP0) * 8;

                if (c & 0x0F) {
                    if (c & 0x03) {
                        if (c & 0x01) {
                            RETURN ( __MKSMALLINT( bitIdx + 1) );
                        } else {
                            RETURN ( __MKSMALLINT( bitIdx + 2) );
                        }
                    } else {
                        if (c & 0x40) {
                            RETURN ( __MKSMALLINT( bitIdx + 3) );
                        } else {
                            RETURN ( __MKSMALLINT( bitIdx + 4) );
                        }
                    }
                } else {
                    if (c & 0x30) {
                        if (c & 0x10) {
                            RETURN ( __MKSMALLINT( bitIdx + 5) );
                        } else {
                            RETURN ( __MKSMALLINT( bitIdx + 6) );
                        }
                    } else {
                        if (c & 0x40) {
                            RETURN ( __MKSMALLINT( bitIdx + 7) );
                        } else {
                            RETURN ( __MKSMALLINT( bitIdx + 8) );
                        }
                    }
                }
                break;
            }
            __sz--;
            __bP++;
        }
        idx0 = __MKSMALLINT( __bP - __bP0 + 1 );
    }
#endif
%}.
    idx0 to:sz do:[:digitIndex |
        (byte := digitByteArray at:digitIndex) ~~ 0 ifTrue:[
            ^ (digitIndex-1)*8 + (byte lowBit)
        ]
    ].
    ^ 0 "/ should not happen

    "
     (1 bitShift:30) lowBit   
     (1 bitShift:30) highBit     
     (1 bitShift:31) lowBit      
     (1 bitShift:31) highBit    
     (1 bitShift:32) lowBit   
     (1 bitShift:32) highBit  
     (1 bitShift:33) lowBit    
     (1 bitShift:33) highBit   
     (1 bitShift:64) lowBit    
     (1 bitShift:64) highBit   
     (1 bitShift:1000) lowBit  
     (1 bitShift:1000) highBit 
     ((1 bitShift:64)-1) lowBit 
     ((1 bitShift:64)-1) highBit 

     1 to:1000 do:[:idx |
        self assert:(( 1 bitShift:idx) lowBit = (idx+1)).
        self assert:(( 1 bitShift:idx) lowBit = ( 1 bitShift:idx) highBit).
        self assert:(( 3 bitShift:idx) lowBit = (idx+1)).
        self assert:(( 7 bitShift:idx) lowBit = (idx+1)).
        self assert:(( 15 bitShift:idx) lowBit = (idx+1)).
        self assert:(( 31 bitShift:idx) lowBit = (idx+1)).
        self assert:(( 63 bitShift:idx) lowBit = (idx+1)).
        self assert:(( 127 bitShift:idx) lowBit = (idx+1)).
        self assert:(( 255 bitShift:idx) lowBit = (idx+1)).
     ]    

     |num|

     num := (1 bitShift:1000).
     Time millisecondsToRun:[
        100000 timesRepeat:[
            num lowBit
        ]
     ]     
    "

    "Modified: 14.8.1997 / 11:55:34 / cg"
! !

!LargeInteger methodsFor:'byte access'!

digitAt:index
    "return 8 bits of value, starting at byte index"

    index > digitByteArray size ifTrue:[^ 0].
    ^ digitByteArray at:index
!

digitAt:index put:aByte
    "set the 8 bits, index is a byte index"

    digitByteArray at:index put:aByte
!

digitByteAt:index
    "return 8 bits of my signed value, starting at byte index.
     For positive receivers, this is the same as #digitAt:;
     for negative ones, the actual bit representation is returned."

    |t digits|
    sign >= 0 ifTrue:[
	index > digitByteArray size ifTrue:[
	    ^ 0
	].
	^ digitByteArray at:index.
    ].

    "/ negative int - do 2's complement here

    t := self bitInvert + 1.
    t sign:1.
    digits := t digitBytes.
    index > digits size ifTrue:[
	^ 16rFF
    ].
    ^ digits at:index.

    "
     16r11111111111111111111 negated digitByteAt:1
     0 asLargeInteger digitByteAt:1 
    "

    "Created: / 25.10.1998 / 14:12:21 / cg"
!

digitBytes
    "return a byteArray filled with the receivers bits
     (8 bits of the absolute value per element).
     Least significant byte is first!!"

    ^ digitByteArray

    "Modified: / 5.5.1999 / 14:57:03 / stefan"
!

digitBytesMSB:msbFlag
    "return a byteArray filled with the receivers bits
     (8 bits of the absolute value per element),
     if msbflag = true, most significant byte is first,
     otherwise least significant byte is first"

    msbFlag ifTrue:[
	^ digitByteArray copyReverse.
    ].
    ^ digitByteArray

    "Modified: / 5.5.1999 / 14:57:03 / stefan"
!

digitLength
    "return the number bytes used by this Integer.
     For negative receivers, the digitLength of its absolute value
     is returned."

    "
     check if there is a 0-byte ...
     this allows to ask unnormalized LargeIntegers 
     for their digitLength
    "
    |l "{ Class: SmallInteger }" |

    l := digitByteArray size.
    [l ~~ 0 and:[(digitByteArray at:l) == 0]] whileTrue:[
	l := l - 1.
    ].
    ^ l

    "Modified: 31.7.1997 / 13:18:28 / cg"
!

digits
    "obsolete, use #digitBytes"

    <resource:#obsolete>

    ^ digitByteArray
! !

!LargeInteger methodsFor:'coercing & converting'!

asLargeInteger
    "return a LargeInteger with same value as myself - thats me"

    ^ self
!

asSmallInteger
    "return a SmallInteger with same value as myself - 
     the result is invalid if the receivers value cannot 
     be represented as a SmallInteger.
     Q: should we raise an exception if this happens ?"

    |value|

    value := 0.
    (sign == 0) ifFalse:[
	digitByteArray reverseDo:[:aDigit |
	    value := (value times:256) + aDigit 
	].
	(sign < 0) ifTrue:[
	    value := value negated
	]
    ].
    ^ value
!

coerce:aNumber
    "return the argument as a LargeInteger"

    ^ aNumber asLargeInteger
!

compressed
    "if the receiver can be represented as a SmallInteger, return
     a SmallInteger with my value; 
     otherwise remove leading zero bytes in the digitByte array
     and return the receiver"

    |index "{ Class: SmallInteger }" 
     val   "{ Class: SmallInteger }" 
     index0
    |

%{  /* NOCONTEXT */
    OBJ t;

    if (__INST(sign) == __MKSMALLINT(0)) {
	RETURN (__MKSMALLINT(0));
    }

    t = __INST(digitByteArray);
    if (__isByteArray(t)) {
	unsigned char *__digitBytes = __ByteArrayInstPtr(t)->ba_element;
	int _idx, _idx0;
	INT _val;

	_idx = _idx0 = __byteArraySize(t);
	while ((_idx > 0) && (__digitBytes[_idx - 1] == 0)) {
	    _idx--;
	}
#ifdef alpha64
	switch (_idx) {
	    case 8:
		_val = __digitBytes[7];
		if (_val <= 0x40) {
		    _val = (_val<<8);
		    _val = (_val + __digitBytes[6]) << 8;
		    _val = (_val + __digitBytes[5]) << 8;
		    _val = (_val + __digitBytes[4]) << 8;
		    _val = (_val + __digitBytes[3]) << 8;
		    _val = (_val + __digitBytes[2]) << 8;
		    _val = (_val + __digitBytes[1]) << 8;
		    _val += __digitBytes[0];
		    if (__INST(sign) == __MKSMALLINT(-1))
			_val = -_val;
		    if (__ISVALIDINTEGER(_val)) {
			RETURN (__MKSMALLINT(_val));
		    }
		}
		break;
	    case 7:
		_val = (__digitBytes[6]<<8);
		_val = (_val + __digitBytes[5]) << 8;
		_val = (_val + __digitBytes[4]) << 8;
		_val = (_val + __digitBytes[3]) << 8;
		_val = (_val + __digitBytes[2]) << 8;
		_val = (_val + __digitBytes[1]) << 8;
		_val += __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    case 6:
		_val = (__digitBytes[5]<<8);
		_val = (_val + __digitBytes[4]) << 8;
		_val = (_val + __digitBytes[3]) << 8;
		_val = (_val + __digitBytes[2]) << 8;
		_val = (_val + __digitBytes[1]) << 8;
		_val += __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    case 5:
		_val = (__digitBytes[4]<<8);
		_val = (_val + __digitBytes[3]) << 8;
		_val = (_val + __digitBytes[2]) << 8;
		_val = (_val + __digitBytes[1]) << 8;
		_val += __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    case 4:
		_val = (__digitBytes[3]<<8);
		_val = (_val + __digitBytes[2]) << 8;
		_val = (_val + __digitBytes[1]) << 8;
		_val += __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    case 3:
		_val = (__digitBytes[2]<<8);
		_val = (_val + __digitBytes[1]) << 8;
		_val += __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    case 2:
		_val = (__digitBytes[1]<<8) + __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    case 1:
		_val = __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    case 0:
		RETURN (__MKSMALLINT(0));

	}
#else
	if (_idx <= 4) {
	    if (_idx <= 2) {
		if (_idx == 0) {
		    RETURN (__MKSMALLINT(0));
		}
		if (_idx == 1) {
		    _val = __digitBytes[0];
		    if (__INST(sign) == __MKSMALLINT(-1))
			_val = -_val;
		    RETURN (__MKSMALLINT(_val));
		}
		_val = (__digitBytes[1]<<8) + __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    }
	    if (_idx == 3) {
		_val = (((__digitBytes[2]<<8) + __digitBytes[1])<<8) + __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		RETURN (__MKSMALLINT(_val));
	    }
	    _val = __digitBytes[3];
	    if (_val <= 0x40) {
		_val = (((((_val<<8) + __digitBytes[2])<<8) + __digitBytes[1])<<8) + __digitBytes[0];
		if (__INST(sign) == __MKSMALLINT(-1))
		    _val = -_val;
		if (__ISVALIDINTEGER(_val)) {
		    RETURN (__MKSMALLINT(_val));
		}
	    }
	}
#endif

	if (_idx == _idx0) {
	    RETURN (self);
	}

	/*
	 * must copy & cut off some bytes
	 */
	{
	    OBJ newDigits;
	    OBJ oldDigits;

	    /*
	     * careful - there is no context here to protect
	     * the receiver ...
	     */
	    __PROTECT__(self);
	    __PROTECT__(__INST(digitByteArray));
	    newDigits = __BYTEARRAY_UNINITIALIZED_NEW_INT(_idx);
	    __UNPROTECT__(oldDigits);
	    __UNPROTECT__(self);
	    if (newDigits) {
		bcopy(__ByteArrayInstPtr(oldDigits)->ba_element,
		      __ByteArrayInstPtr(newDigits)->ba_element,
		      _idx);
		__INST(digitByteArray) = newDigits; __STORE(self, newDigits);
		RETURN (self);
	    }
	    /*
	     * allocation failed ...
	     * ... fall through to trigger the error
	     */
	}
    }
%}.
    index0 := index := digitByteArray size.
    [(index > 0) and:[(digitByteArray at:index) == 0]] whileTrue:[
	index := index - 1
    ].
"/    ((index < SmallInteger maxBytes) 
"/    or:[(index == SmallInteger maxBytes) 
"/            and:[(digitByteArray at:index) < 16r20]])
"/    ifTrue:[
"/        val := 0.
"/        1 to:index do:[:i |
"/            val := val bitShift:8.
"/            val := val bitOr:(digitByteArray at:i).
"/        ].
"/        ^ val * sign
"/    ].
    (index ~~ index0) ifTrue:[
	digitByteArray := digitByteArray copyFrom:1 to:index
    ].
    ^ self
!

generality
    "return the generality value - see ArithmeticValue>>retry:coercing:"

    ^ 40
!

value:aSmallInteger
    "setup my contents to represent the same value as aSmallInteger.
     This method will fail, if the argument is not a smallInteger.
     This should only be used internally, 
     since it will create an unnormalized LargeInt (by purpose) if asked for."

    |absValue 
     b1 "{ Class: SmallInteger }"
     b2 "{ Class: SmallInteger }"
     b3 "{ Class: SmallInteger }"
     b4 "{ Class: SmallInteger }"
     b5 "{ Class: SmallInteger }"
     b6 "{ Class: SmallInteger }"
     b7 "{ Class: SmallInteger }"|

    "
     could have simply created a 4-byte largeinteger and normalize it. 
     The code below does the normalize right away, avoiding the
     overhead of producing any intermediate byte-arrays (and the scanning)
    "
    (aSmallInteger == 0) ifTrue: [
	digitByteArray := ByteArray with:0.
	sign := 0.
	^ self
    ].

    (aSmallInteger < 0) ifTrue: [
	sign := -1.
	absValue := aSmallInteger negated
    ] ifFalse: [
	sign := 1.
	absValue := aSmallInteger
    ].

    b1 := absValue bitAnd:16rFF.
    absValue := absValue bitShift:-8.
    absValue == 0 ifTrue:[
	digitByteArray := ByteArray with:b1
    ] ifFalse:[
	b2 := absValue bitAnd:16rFF.
	absValue := absValue bitShift:-8.
	absValue == 0 ifTrue:[
	    digitByteArray := ByteArray with:b1 with:b2
	] ifFalse:[
	    b3 := absValue bitAnd:16rFF.
	    absValue := absValue bitShift:-8.
	    absValue == 0 ifTrue:[
		digitByteArray := ByteArray with:b1 with:b2 with:b3
	    ] ifFalse:[
		b4 := absValue bitAnd:16rFF.
		absValue := absValue bitShift:-8.
		absValue == 0 ifTrue:[
		    digitByteArray := ByteArray with:b1 with:b2 with:b3 with:b4
		] ifFalse:[
		    b5 := absValue bitAnd:16rFF.
		    absValue := absValue bitShift:-8.
		    absValue == 0 ifTrue:[
			digitByteArray := ByteArray new:5.
			digitByteArray at:1 put:b1.
			digitByteArray at:2 put:b2.
			digitByteArray at:3 put:b3.
			digitByteArray at:4 put:b4.
			digitByteArray at:5 put:b5.
		    ] ifFalse:[
			b6 := absValue bitAnd:16rFF.
			absValue := absValue bitShift:-8.
			absValue == 0 ifTrue:[
			    digitByteArray := ByteArray new:6.
			    digitByteArray at:1 put:b1.
			    digitByteArray at:2 put:b2.
			    digitByteArray at:3 put:b3.
			    digitByteArray at:4 put:b4.
			    digitByteArray at:5 put:b5.
			    digitByteArray at:6 put:b6.
			] ifFalse:[
			    b7 := absValue bitAnd:16rFF.
			    absValue := absValue bitShift:-8.
			    absValue == 0 ifTrue:[
				digitByteArray := ByteArray new:7.
				digitByteArray at:1 put:b1.
				digitByteArray at:2 put:b2.
				digitByteArray at:3 put:b3.
				digitByteArray at:4 put:b4.
				digitByteArray at:5 put:b5.
				digitByteArray at:6 put:b6.
				digitByteArray at:7 put:b7.
			    ] ifFalse:[
				digitByteArray := ByteArray new:8.
				digitByteArray at:1 put:b1.
				digitByteArray at:2 put:b2.
				digitByteArray at:3 put:b3.
				digitByteArray at:4 put:b4.
				digitByteArray at:5 put:b5.
				digitByteArray at:6 put:b6.
				digitByteArray at:7 put:b7.
				digitByteArray at:8 put:absValue.
			    ]
			]
		    ]
		]
	    ]
	]
    ]

    "Modified: / 26.5.1999 / 22:18:14 / cg"
! !

!LargeInteger methodsFor:'comparing'!

< aNumber
    "return true, if the argument, aNumber is greater than the receiver"

    |otherSign|

    (aNumber class == self class) ifFalse:[
        ^ aNumber lessFromInteger:self
    ].
    otherSign := aNumber sign.

    (sign > 0) ifTrue:[
        "I am positive"
        (otherSign > 0) ifTrue:[^ self absLess:aNumber].
        ^ false "aNumber is <= 0"
    ].
    (sign == 0) ifTrue:[
        (otherSign > 0) ifTrue:[^ true].
        ^ false
    ].
    "I am negative"
    (otherSign > 0) ifTrue:[^ true].
    (otherSign == 0) ifTrue:[^ true].
    ^ (aNumber absLess:self)

    "Modified: / 31.7.2002 / 10:08:19 / cg"
!

= aNumber
    "return true, if the argument represents the same numeric value
     as the receiver, false otherwise"

    "/ speed up compare to 0

    (aNumber == 0) ifTrue:[
        ^ sign == 0
    ].

    (aNumber class == self class) ifFalse:[
        "/
        "/ here, we depend on the fact, that largeinteger
        "/ results are always converted to smallInts, if possible.
        "/ therefore, a largeInt in the smallInt range is not allowed (possible)
        "/
        aNumber class == SmallInteger ifTrue:[^ false ].
        ^ aNumber equalFromInteger:self
    ].

    (aNumber sign == sign) ifFalse:[^ false].
    ^ self absEq:aNumber

    "Modified: / 13.2.1998 / 11:43:15 / stefan"
!

> aNumber
    "return true, if the argument, aNumber is less than the receiver"

    |otherSign|

    (aNumber class == self class) ifFalse:[
        ^ (aNumber < self)
    ].
    otherSign := aNumber sign.

    (sign > 0) ifTrue:[
        "I am positive"
        (otherSign > 0) ifTrue:[^ aNumber absLess:self].
        ^ true "aNumber is <= 0"
    ].
    (sign == 0) ifTrue:[
        "I am zero"
        (otherSign > 0) ifTrue:[^ false].
        ^ true
    ].
    "I am negative"
    (otherSign > 0) ifTrue:[^ false].
    (otherSign == 0) ifTrue:[^ false].
    ^ (self absLess:aNumber)

    "Modified: / 31.7.2002 / 10:08:59 / cg"
!

hash
    "return an integer useful for hashing on large numbers"

    ^ (self bitAnd:16r3FFFFFFF) + digitByteArray size
! !

!LargeInteger methodsFor:'double dispatching'!

differenceFromInteger:anInteger
    "sent, when anInteger does not know how to subtract the receiver.
     Return the result of 'anInteger - self'. The argument must be a SmallInteger."

    anInteger > 0 ifTrue:[
	sign > 0 ifTrue:[
	    ^ self absFastMinus:anInteger sign:-1
	].
	^ self absFastPlus:anInteger sign:1
    ].
    anInteger == 0 ifTrue:[
	^ self negated
    ].
    sign > 0 ifTrue:[
	^ self absFastPlus:anInteger negated sign:-1
    ].
    ^ self absFastMinus:anInteger sign:-1

    "
     12345678901234567890          
     -12345678901234567890         
     12345678901234567890 differenceFromInteger:0       
     12345678901234567890 differenceFromInteger:1       
     12345678901234567890 differenceFromInteger:-1      
     -12345678901234567890 differenceFromInteger:1   
     -12345678901234567890 differenceFromInteger:-1   
    "

    "Modified: 20.10.1996 / 18:41:54 / cg"
!

productFromInteger:anInteger
    "sent, when anInteger does not know how to multiply the receiver.
     Return the product of the receiver and the argument, aSmallInteger"

    |num result 
     resultDigitByteArray
     val     "{ Class: SmallInteger }"
     len     "{ Class: SmallInteger }"
     carry   "{ Class: SmallInteger }"
     prod    "{ Class: SmallInteger }" 
     ok lResult|

    "multiplying by a small integer is done here"

    "trivial cases"
    anInteger == 0 ifTrue:[^ 0].
    anInteger == 1 ifTrue:[^ self].

    num := anInteger abs.
    (num > 16r3FFFFF) ifTrue:[
	"if num is too big (so that multiplying by a byte could create a Large)"

	^ anInteger retry:#* coercing:self
    ].

    len := digitByteArray size.

    val := num.
    val <= 16rFF ifTrue:[
	lResult := len + 1.
    ] ifFalse:[
	val <= 16rFFFF ifTrue:[
	    lResult := len + 2
	] ifFalse:[
	    val <= 16rFFFFFF ifTrue:[
		lResult := len + 4.
	    ] ifFalse:[
		lResult := len + 6.
	    ]
	]
    ].
    resultDigitByteArray := ByteArray uninitializedNew:lResult.
    result := self class basicNew setDigits:resultDigitByteArray.

    anInteger < 0 ifTrue:[
	sign > 0 ifTrue:[
	    result sign:-1
	].
    ] ifFalse:[
	sign < 0 ifTrue:[
	    result sign:sign
	]
    ].

    ok := false.
%{
    OBJ __digitByteArray = __INST(digitByteArray);

    if (__isSmallInteger(len)
     && __isByteArray(__digitByteArray)
     && __isByteArray(resultDigitByteArray)) {
	INT _l = __intVal(len);
	INT _v = __intVal(val);
	unsigned INT _carry = 0;
	unsigned INT _prod;
	unsigned char *digitP = __ByteArrayInstPtr(__digitByteArray)->ba_element;
	unsigned char *resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;

	/*
	 * skipping zeros does not help much (a few percent) on
	 * a P5 or other CPUS with a fast multiplier. 
	 * It may make more of a difference on CPUs with slower 0-multiply.
	 */
	while ((_l >= sizeof(INT)) && (((unsigned INT *)digitP)[0] == 0)) {
	     ((unsigned long *)resultP)[0] = 0;
	    digitP += sizeof(INT);
	    resultP += sizeof(INT);
	    _l -= sizeof(INT);
	}

#if defined(i386) || defined(alpha) /* XXX actually: LSB_FIRST */
# if defined (__GNUC__) && defined(i386)
	/*
	 * can do it long-word-wise;
	 * 32*32 -> 64 multiplication
	 */
	while (_l > 3) {
	    unsigned __pHi, __pLow;
	    unsigned __digit;

	    /* 
	     * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
	     * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
	     */
	    __digit = ((unsigned long *)digitP)[0];
	    asm ("mull %3               \n\
		  addl %4,%%eax         \n\
		  adcl $0,%%edx"    
		    : "=a"  (__pLow),
		      "=d"  (__pHi)
		    : "0"   (__digit),
		      "1"   ((unsigned long)(_v)),
		      "rm"  ((unsigned long)(_carry)) );

	    ((unsigned long *)resultP)[0] = __pLow;
	    _carry = __pHi;
	    digitP += 4;
	    resultP += 4;
	    _l -= 4;
	}
# else /* not GNU-i386 */
#  if defined (WIN32) && defined(i386)
	/*
	 * can do it long-word-wise;
	 * 32*32 -> 64 multiplication
	 */
	while (_l > 3) {
	    unsigned __pLow;
	    unsigned digit; 

	    /* 
	     * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
	     * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
	     */
/*
	    digit = ((unsigned long *)digitP)[0]; 
	    edx::eax = (digit * _v);
	    edx::eax += _carry;
	    ((unsigned long *)resultP)[0] = eax; -- pLow
	    _carry = edx; -- pHigh
	    digitP += 4;
	    resultP += 4;
*/
	    digit = ((unsigned long *)digitP)[0];
	    asm {
		mov   eax, digit
		mov   edx, _v
		mul   edx
		add   eax, _carry
		adc   edx, 0 
		mov   __pLow, eax
		mov   _carry, edx
	    }

	    ((unsigned long *)resultP)[0] = __pLow; 
	    digitP += 4; 
	    resultP += 4; 
	    _l -= 4;
	}
#  else /* not WIN32-i386 */
#   if defined(INT64)
	if (_v <= 0xFFFFFFFFL) {
	    /*
	     * have a 64bit int type ... good
	     */
	    UINT64 _prod64;

	    /* have 64bit ints; can do it int-wise
	     *
	     * max: 0xFFFFFFFF * 0xFFFFFFFF -> 0xFFFFFFFE.0001
	     * + maxCarry (0xFFFFFFFF)  -> 0xFFFFFFFF.0000
	     */
	    while (_l > 3) {
		unsigned __t;

		__t = ((unsigned *)digitP)[0];
		digitP += 4;
		_prod64 = (INT64)_v;
		_prod64 *= __t;
		_prod64 += _carry;
		((unsigned *)resultP)[0] = _prod64 /* & 0xFFFFFFFFL */;
		_carry = _prod64 >> 32;
		resultP += 4;
		_l -= 4;
	    }
	    if (_l > 1) {
		unsigned short __t;

		__t = ((unsigned short *)digitP)[0];
		digitP += 2;
		_prod64 = (INT64)_v;
		_prod64 *= __t;
		_prod64 += _carry;
		((unsigned short *)resultP)[0] = _prod64 /* & 0xFFFF */;
		_carry = _prod64 >> 16;
		resultP += 2;
		_l -= 2;
	    }
	    if (_l > 0) {
		_prod64 = *digitP++ * _v + _carry;
		*resultP++ = _prod64 /* & 0xFF */;
		_carry = _prod64 >> 8;
		_l--;
	    }
	}
#   else /* no INT64 type */
	if (_v <= 0xFFFF) {
	    /* can do it short-wise 
	     * 
	     * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
	     * + maxCarry (0xFFFF)  -> 0xFFFF.0000
	     */
	    while (_l > 1) {
		_prod = ((unsigned short *)digitP)[0] * _v + _carry;
		((unsigned short *)resultP)[0] = _prod /* & 0xFFFF */;
		_carry = _prod >> 16;
		digitP += 2;
		resultP += 2;
		_l -= 2;
	    }
	}
#   endif /* no INT64 */
#  endif /* not WIN32-i386 */
# endif /* not GNU-i386 */
#else /* not LSB_FIRST */

# ifdef mips
#  define LOAD_WORD_WISE
   /* no, STORE_WORD_WISE makes it slower */
# endif

	if (_v <= 0xFFFF) {
	    /* can do it short-wise 
	     * 
	     * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
	     * + maxCarry (0xFFFF)  -> 0xFFFF.0000
	     */
	    while (_l > 1) {
		unsigned int t;

#if defined(LOAD_WORD_WISE)
		/* better fetch short-wise */
		t = ((unsigned short *)digitP)[0];
		digitP += 2;
		t = ((t >> 8) | (t << 8)) & 0xFFFF;
#else
		t = (digitP[1]<<8) + digitP[0];
		digitP += 2;
#endif
		_prod = t * _v + _carry;
		_carry = _prod >> 16;
#if defined(STORE_WORD_WISE)
		/* better store short-wise */
		_prod = ((_prod >> 8) | (_prod << 8)) & 0xFFFF;
		((unsigned short *)resultP)[0] = _prod;
#else
		resultP[0] = _prod /* & 0xFF */;
		resultP[1] = (_prod>>8) /* & 0xFF */;
#endif
		resultP += 2;
		_l -= 2;
	    }
	}

#endif /* LSB_FIRST */

	/*
	 * rest is done byte-wise
	 */
	while (_l > 0) {
	    _prod = *digitP++ * _v + _carry;
	    *resultP++ = _prod /* & 0xFF */;
	    _carry = _prod >> 8;
	    _l--;
	}

	_l = __intVal(lResult) - __intVal(len);

	/*
	 * remaining carry
	 */
	while (_carry) {
	    *resultP++ = _carry /* & 0xFF */;
	    _carry >>= 8;
	    _l--;
	}

	/*
	 * remaining zeros
	 */
	while (_l--) {
	    *resultP++ = 0;
	}

	/*
	 * need compress ?
	 */
	if (resultP[-1]) {
	    /*
	     * no
	     */
	    RETURN(result);
	}

	ok = true;
    }
%}.
    "
     fall back - normally not reached
     (could make it a primitive-failure as well)
    "
    ok ifFalse:[
	carry := 0.
	1 to:len do:[:i |
	    prod := (digitByteArray basicAt:i) * val + carry.
	    resultDigitByteArray basicAt:i put:(prod bitAnd:16rFF).
	    carry := prod bitShift:-8.
	].
	[carry ~~ 0] whileTrue:[
	    len := len + 1.
	    resultDigitByteArray basicAt:len put:(carry bitAnd:16rFF).
	    carry := carry bitShift:-8
	].
	[len < lResult] whileTrue:[
	    len := len + 1.
	    resultDigitByteArray basicAt:len put:0
	]
    ].
    ^ result compressed
!

sumFromInteger:anInteger
    "sent, when anInteger does not know how to add the receiver.
     Return the sum of the receiver and the argument, (which must be a SmallInteger)"

    anInteger > 0 ifTrue:[
	sign > 0 ifTrue:[
	    ^ self absFastPlus:anInteger sign:1
	].
	^ self absFastMinus:anInteger sign:-1
    ].
    anInteger == 0 ifTrue:[
	^ self
    ].
    sign > 0 ifTrue:[
	^ self absFastMinus:anInteger sign:1
    ].
    ^ self absFastPlus:anInteger sign:-1


    "
     12345678901234567890          
     -12345678901234567890         
     12345678901234567890 sumFromInteger:0       
     -12345678901234567890 sumFromInteger:0       
     12345678901234567890 sumFromInteger:1       
     12345678901234567890 sumFromInteger:-1      
     -12345678901234567890 sumFromInteger:1     
     -12345678901234567890 sumFromInteger:-1   
    "

    "Modified: / 9.1.1998 / 13:27:37 / cg"
! !

!LargeInteger methodsFor:'printing & storing'!

xxxstoreOn:aStream
    "append a representation of the receiver to aStream, which can
     be used to reconstruct the receiver."

    aStream nextPutAll:'('.
    self printOn:aStream.
    aStream nextPutAll:' asLargeInteger)'
! !

!LargeInteger methodsFor:'private'!

absDivMod:anInteger
    "return an array with two LargeIntegers representing
     abs(self) // abs(theArgument) and abs(self) \\ abs(theArgument).
     Used as a helper for \\, //, rem: and quo:.
     This method needs a rewrite."

    |dividend divisor 
     quo digits
     shift "{ Class: SmallInteger }" |

    anInteger == 0 ifTrue:[
        ^ ZeroDivide raiseRequestWith:thisContext
    ].

    self = anInteger ifTrue:[
        ^ Array with:1 with:0
    ].

    shift := self highBit - anInteger highBit.
    dividend := LargeInteger digitBytes:digitByteArray copy. "/ self simpleDeepCopy sign:1.
    shift < 0 ifTrue:[
        ^ Array with:0 with:dividend compressed.
    ].
    shift == 0 ifTrue:[
        divisor := LargeInteger digitBytes:(anInteger digitBytes copy). "/ anInteger simpleDeepCopy.
    ] ifFalse:[
        divisor := anInteger bitShift:shift.
    ].

    quo := self class basicNew numberOfDigits:((shift // 8) + 1). 
    digits := quo digitBytes.

    shift := shift + 1.
    [shift > 0] whileTrue:[
        (dividend absLess:divisor) ifFalse:[
            digits bitSetAt:shift.
            (dividend absSubtract: divisor) ifFalse:[ "result == 0"
                ^ Array with:quo compressed with:dividend compressed            
            ].
        ].
        shift := shift - 1.
        divisor div2.
    ].
    ^ Array with:quo compressed with:dividend compressed

    "
     Time millisecondsToRun:[ 10000 timesRepeat:[  16000000000 absDivMod:4000000000] ]  
     Time millisecondsToRun:[ 10000 timesRepeat:[  16000000000 absDivMod:3000000000] ]  
     16000000000 absDivMod:4000000000 
     16000000000 absDivMod:3000000000
    "

    "Modified: / 5.11.1996 / 18:40:24 / cg"
    "Created: / 27.4.1999 / 19:45:44 / stefan"
    "Modified: / 26.7.1999 / 10:46:36 / stefan"
!

absEq:aLargeInteger
    "return true, if abs(self) = abs(theArgument)"

    |len1 "{ Class: SmallInteger }"
     len2 "{ Class: SmallInteger }"
     d1   "{ Class: SmallInteger }"
     d2   "{ Class: SmallInteger }"
     otherDigitByteArray |

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digitBytes.
    len2 := otherDigitByteArray size.

    "/ the highest digit(s) should not be zero
    "/ when properly normalized; 
    "/ but we are tolerant here, to allow for unnormalized
    "/ numbers to be compared ...

    [(digitByteArray basicAt:len1) == 0] whileTrue:[
	len1 := len1 - 1
    ].
    [(otherDigitByteArray basicAt:len2) == 0] whileTrue:[
	len2 := len2 - 1
    ].
    (len1 ~~ len2) ifTrue:[^ false].
    [len1 > 0] whileTrue:[
	d1 := digitByteArray basicAt:len1.
	d2 := otherDigitByteArray basicAt:len1.
	(d1 ~~ d2) ifTrue:[^ false].
	len1 := len1 - 1
    ].
    ^ true

    "Modified: / 8.5.1999 / 18:37:02 / cg"
!

absFastDivMod:aPositiveSmallInteger
    "return an array with two LargeIntegers representing
     abs(self) // aPositiveSmallInteger and 
     abs(self) \\ aPositiveSmallInteger."

    |tmp1     "{ Class: SmallInteger }"
     prevRest "{ Class: SmallInteger }"
     count    "{ Class: SmallInteger }"
     newDigitByteArray result
     ok|

    aPositiveSmallInteger == 0 ifTrue:[
        ^ ZeroDivide raiseRequestWith:thisContext
    ].

"This cannot happen (if always normalized)
    self < aPositiveSmallInteger ifTrue:[
        ^ Array with:0 with:self
    ].
"
    count := digitByteArray size.
    result := self class basicNew numberOfDigits:count.
    newDigitByteArray := result digitBytes.
    ok := false.
%{
    OBJ __digits;

    __digits = __INST(digitByteArray);

    if (__isByteArray(__digits)
     && __isByteArray(newDigitByteArray)
     && __bothSmallInteger(count, aPositiveSmallInteger)) {
        unsigned INT rest = 0;
        int index = __intVal(count);
        int index0;
        unsigned INT divisor = __intVal(aPositiveSmallInteger);
        unsigned char *digitBytes = __ByteArrayInstPtr(__digits)->ba_element;
        unsigned char *resultBytes = __ByteArrayInstPtr(newDigitByteArray)->ba_element;

        index0 = index - 1;

        /* 
         * divide short-wise 
         */
        if (divisor <= 0xFFFF) {
            if ((index & 1) == 0) { /* even number of bytes */
                while (index > 1) {
                    unsigned INT t;
                    unsigned INT div;

                    index -= 2;
#if defined(__LSBFIRST) || defined(i386)
                    t = *((unsigned short *)(&digitBytes[index]));
#else
                    t = digitBytes[index+1];
                    t = (t << 8) | digitBytes[index];
#endif
                    t = t | (rest << 16);
                    div = t / divisor;
                    rest = t % divisor;
#if defined(__LSBFIRST) || defined(i386)
                    *((unsigned short *)(&resultBytes[index])) = (div & 0xFFFF);
#else
                    resultBytes[index+1] = div >> 8;
                    resultBytes[index] = div /* & 0xFF */;
#endif
                }
            }
        }
        while (index > 0) {
            unsigned INT t;

            index--;
            t = digitBytes[index];
            t = t | (rest << 8);
            resultBytes[index] = t / divisor;
            rest = t % divisor;
        }
        prevRest = __MKSMALLINT(rest);

        /*
         * no need to normalize ?
         */
        while ((index0 >= sizeof(INT)) && (resultBytes[index0]==0)) {
            index0--;
        }

        if (index0 > sizeof(INT)) {
            RETURN ( __ARRAY_WITH2(result, prevRest));
        }
        if ((index0 == sizeof(INT))
         && resultBytes[index0] >= 0x40) {
            RETURN ( __ARRAY_WITH2(result, prevRest));
        }
        /*
         * must compress
         */
        ok = true;
    }
%}.
    "
     slow code - not normally reached
     (could also do a primitiveFailure here)
    "
    ok ifFalse:[
        ^ self absDivMod:(LargeInteger value:aPositiveSmallInteger).
    ].

    ^ Array with:(result compressed) with:prevRest

    "
     16r123412341234 asLargeInteger absDivMod:(LargeInteger value:10) 
     ((16r1234 asLargeInteger absFastDivMod:16rffff) at:2) printStringRadix:16
     ((16r00123456 asLargeInteger absFastDivMod:16rffffff) at:2) printStringRadix:16  
     ((666666666666666666 asLargeInteger absFastDivMod:16r3))  
     ((1666666666 asLargeInteger absFastDivMod:16r3))  
    "
!

absFastMinus:aSmallInteger sign:newSign
    "return a LargeInteger representing abs(self) - abs(theArgument)
     with sign: newSign.
     The result is normalized.
     This is a helper for addition and subtraction - not for public use."

    |result resultDigitByteArray lastDigit ok
     len     "{ Class: SmallInteger }"
     rsltLen "{ Class: SmallInteger }"
     index   "{ Class: SmallInteger }"
     borrow  "{ Class: SmallInteger }"
     diff    "{ Class: SmallInteger }" |

    "/ the following code only works with
    "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255

    ((aSmallInteger < (SmallInteger minVal + 255))
    or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
	^ self absMinus:(LargeInteger value:aSmallInteger) sign:newSign.
    ]. 

    len := digitByteArray size.

    rsltLen := len "+ 1".
    result := self class basicNew numberOfDigits:rsltLen.
    result sign:newSign.
    resultDigitByteArray := result digitBytes.

    borrow := aSmallInteger abs.

%{
    if (__isByteArray(__INST(digitByteArray))
     && __isByteArray(resultDigitByteArray)) {
	unsigned INT __borrow = __intVal(borrow);
	INT __diff;
	int __index = 1;
	int __len = __intVal(len);
	unsigned char *__digitP = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
	unsigned char *__resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
	int __len3;

#if defined(alpha64)
	/* 
	 * subtract int-wise 
	 */
	__len3 = __len - 3;
	while (__index < __len3) {
	    /* do not make this into one expression - ask cg why */
	    __diff = ((unsigned int *)(__digitP + __index-1))[0];
	    __diff -= (__borrow & 0xFFFFFFFFL);
	    __borrow >>= 32;
	    if (__diff < 0) {
		/* __diff += 0x100000000; */
		__borrow++;
	    }
	    ((unsigned int *)(__resultP+__index-1))[0] = __diff;
	    __index += 4;
	}
#endif
#if defined(__LSBFIRST) || defined(i386)
	/* 
	 * subtract short-wise 
	 */
	while (__index < __len) {
	    /* do not make this into one expression - ask cg why */
	    __diff = ((unsigned short *)(__digitP+__index-1))[0];
	    __diff -= (__borrow & 0xFFFF);
	    __borrow >>= 16;
	    if (__diff < 0) {
		/* __diff += 0x10000; */
		__borrow++;
	    } else {
		if (__borrow == 0) {
		    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
		    __index += 2;

		    /* nothing more to subtract .. */
		    while (__index < __len) {
			((unsigned short *)(__resultP+__index-1))[0] = ((unsigned short *)(__digitP+__index-1))[0];
			__index += 2;
		    }
		    if (__index <= __len) {
			__resultP[__index-1] = __digitP[__index-1];
		    }
		    break;
		}
	    }
	    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
	    __index += 2;
	}
#endif
	/* 
	 * subtract byte-wise 
	 */
	while (__index <= __len) {
	    __diff = __digitP[__index-1];
	    __diff -= (__borrow & 0xFF);
	    __borrow >>= 8;
	    if (__diff < 0) {
		/* __diff += 0x100; */
		__borrow++;
	    } else {
		if (__borrow == 0) {
		    __resultP[__index-1] = __diff;
		    __index++;

		    /* nothing more to subtract .. */
		    while (__index <= __len) {
			__resultP[__index-1] = __digitP[__index-1];
			__index++;
		    }
		    break;
		}
	    }
	    __resultP[__index-1] = __diff;
	    __index++;
	}
	lastDigit = __MKSMALLINT( __resultP[__index-1-1] );
	ok = true;
    }
%}.

    ok == true ifFalse:[        "/ cannot happen
	index := 1.
	[borrow ~~ 0] whileTrue:[
	    (index <= len) ifTrue:[
		diff := (digitByteArray basicAt:index) - (borrow bitAnd:16rFF).
		borrow := borrow bitShift:-8.
		diff < 0 ifTrue:[
		    diff := diff + 256.
		    borrow := borrow + 1.
		]
	    ] ifFalse:[
		diff := borrow bitAnd:255.
		borrow := borrow bitShift:-8.
	    ].
	    resultDigitByteArray basicAt:index put:(lastDigit := diff).
	    index := index + 1
	].
	[index <= len] whileTrue:[
	    resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
	    index := index + 1
	].
	(index <= rsltLen) ifTrue:[
	    lastDigit := 0.
	]
    ].

    (lastDigit == 0 or:[rsltLen <= SmallInteger maxBytes]) ifTrue:[ 
	^ result compressed.
    ]. 
    ^ result

    "                                                          
     12345678900000000000 absFastMinus:1 sign:1       
     12345678900000000000 absFastMinus:1 sign:-1      
     12345678900000000000 absFastMinus:1000000 sign:1 
     12345678900000000000 absFastMinus:255 sign:1     
     (SmallInteger maxVal + 1) absFastMinus:1 sign:1
     (SmallInteger minVal - 1) absFastMinus:1 sign:1  
    "

    "Modified: 24.3.1997 / 21:33:25 / cg"
!

absFastPlus:aSmallInteger sign:newSign
    "return a LargeInteger representing abs(self) + abs(theArgument).
     with sign: newSign.
     The result is normalized. The argument must be a smallInteger
     with byteSize one less than the integer byteSize.
     This is a helper for addition and subtraction - not for public use."

    |result resultDigitByteArray lastDigit
     ok
     len     "{ Class: SmallInteger }"
     rsltLen "{ Class: SmallInteger }"
     index "{ Class: SmallInteger }"
     carry "{ Class: SmallInteger }" |

    "/ the following code only works with
    "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255

    ((aSmallInteger < (SmallInteger minVal + 255))
    or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
	^ self absPlus:(LargeInteger value:aSmallInteger) sign:newSign.
    ]. 

    len := rsltLen := digitByteArray size.
    "/
    "/ there can only be an overflow from the high byte,
    "/ if it is 255 (since the other number is definitely smaller)
    "/
    (digitByteArray at:len) == 16rFF ifTrue:[
	rsltLen := len + 1.
    ] ifFalse:[
	"/ or the argument has something in the high byte ..
%{
#ifdef alpha64
	if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
	    rsltLen = __MKSMALLINT(__intVal(len) + 1);
	}
#else
	if (__intVal(aSmallInteger) & 0xFF000000) {
	    rsltLen = __MKSMALLINT(__intVal(len) + 1);
	}
#endif
%}
    ].

    result := self class basicNew numberOfDigits:rsltLen.
    result sign:newSign.
    resultDigitByteArray := result digitBytes.

%{
    if (__isByteArray(__INST(digitByteArray))
     && __isByteArray(resultDigitByteArray)
     && __isSmallInteger(aSmallInteger)) {
	/* carry is NOT unsigned (see negation below) */
	INT __carry = __intVal(aSmallInteger);
	int __index = 1;
	int __len = __intVal(len);
	unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
	unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
	INT __ptrDelta = __dst - __src;
	unsigned char *__srcLast = __src + __len - 1;
	int __rsltLen = __intVal(rsltLen);

	if (__carry < 0) {
	    __carry = -__carry;
	}

#if defined(__LSBFIRST) || defined(i386) || defined(alpha)
# if defined(i386) && defined(__GNUC__)
#  if 0 /* NOTICE - the code below is 20% slower ... - why */
	/*
	 * add long-wise
	 */
	asm("  jecxz nothingToDo                                      \n\
	       movl  %%eax, %%esi      /* __src input */              \n\
	       movl  %%ebx, %%edi      /* __dst input */              \n\
								      \n\
	       /* the first 4-byte int */                             \n\
	       lodsl                   /* fetch */                    \n\
	       addl  %%edx, %%eax      /* add */                      \n\
	       stosl                   /* store */                    \n\
	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
	       jecxz doneLoop          /* any more ? */               \n\
	       /* remaining 4-byte ints */                            \n\
	       jmp   addLoop                                          \n\
								      \n\
	       .align 8                                               \n\
	     addLoop:                                                 \n\
	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
	       jnc   copyLoop2                                        \n\
	       movl  $0, %%eax                                        \n\
	       leal  4(%%esi), %%esi                                  \n\
	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
	       leal  8(%%edi), %%edi                                  \n\
	       movl  %%eax, -8(%%edi)  /* store */                    \n\
	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
	       jecxz doneLoop          /* any more ? */               \n\
								      \n\
	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
	       movl  $0, %%eax                                        \n\
	       leal  4(%%esi), %%esi                                  \
	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
	       movl  %%eax, -4(%%edi)  /* store */                    \n\
								      \n\
	       loop  addLoop                                          \n\
	       jmp   doneLoop                                         \n\
								      \n\
	       .align 8                                               \n\
	     copyLoop:                                                \n\
	       movl  0(%%esi), %%ebx                                  \n\
	     copyLoop2:                                               \n\
	       add   $4, %%esi                                        \n\
	       add   $4, %%edi                                        \n\
	       movl  %%ebx, -4(%%edi)                                 \n\
	       loop  copyLoop                                         \n\
								      \n\
	     doneLoop:                                                \n\
	       movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
	       adcl  $0, %%edx                                        \n\
	       movl  %%esi, %%eax      /* __src output */             \n\
	     nothingToDo:                                             \n\
	    " : "=d"  ((unsigned long)(__carry)),
		"=a"  (__src)
	      : "1"   (__src),
		"b"   (__dst),
		"c"   (__len / 4),
		"0"   (__carry)
	      : "esi", "edi");

#  else
	{
	    unsigned char *__srcLastX;

	    __srcLastX = __srcLast - 3 - 4;
	    while (__src <= __srcLastX) {
		unsigned int __sum, __sum2;
		unsigned __digit1, __digit2;

		__digit1 = ((unsigned *)__src)[0];
		__digit2 = ((unsigned *)__src)[1];
		asm ("addl %%edx,%%ecx          \n\
		      adcl $0, %%eax            \n\
		      movl $0, %%edx            \n\
		      adcl $0, %%edx"    
			: "=d"  ((unsigned long)(__carry)),
			  "=c"  ((unsigned long)(__sum)),
			  "=a"  ((unsigned long)(__sum2))
			: "0"   ((unsigned long)(__carry)),
			  "1"   (__digit1),
			  "2"   (__digit2));

		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
		((unsigned int *)(__src + __ptrDelta))[1] = __sum2;

		__src += 8;  

		if (__carry == 0) {
		    while (__src <= __srcLastX) {
			/* copy over words */
			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
			((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
			__src += 8;
		    }
		    while (__src <= __srcLast) {
			/* copy over bytes */
			__src[__ptrDelta] = __src[0];
			__src ++;
		    }
		    goto doneSource;
		}
	    }

	    __srcLastX = __srcLastX + 4;
	    if (__src <= __srcLastX) {
		unsigned int __sum, __digit;

		__digit = ((unsigned *)__src)[0];

		asm ("addl %%eax,%%edx  \n\
		      movl $0,%%eax     \n\
		      adcl $0,%%eax"    
			: "=a"  ((unsigned long)(__carry)),
			  "=d"  ((unsigned long)(__sum))
			: "0"   ((unsigned long)(__carry)),
			  "1"   (__digit) );

		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
		__src += 4;  

		if (__carry == 0) {
		    while (__src <= __srcLast) {
			/* copy over bytes */
			__src[__ptrDelta] = __src[0];
			__src ++;
		    }
		    goto doneSource;
		}
	    }
	}
#  endif
# else 
#  if defined(i386) && defined(WIN32)
	{
	    unsigned char *__srcLast4;

	    /*
	     * add long-wise
	     */
	    __srcLast4 = __srcLast - 3;
	    while (__src <= __srcLast4) {
		unsigned int __sum;

		__sum = ((unsigned int *)__src)[0];    
		asm {
		      mov eax, __sum
		      add eax, __carry
		      mov edx, 0
		      adc edx, 0
		      mov __sum, eax
		      mov __carry, edx
		    }

		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
		__src += 4;  
		if (__carry == 0) {
		    while (__src <= __srcLast4) {
			/* copy over words */
			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
			__src += 4;
		    }
		    while (__src <= __srcLast) {
			/* copy over bytes */
			__src[__ptrDelta] = __src[0];
			__src ++;
		    }
		    goto doneSource;
		}
	    }
	}
#  else 
#   ifdef alpha64
	{
	    unsigned char *__srcLast4;

	    /*
	     * add long-wise
	     */
	    __srcLast4 = __srcLast - 3;
	    while (__src <= __srcLast4) {
		unsigned INT __sum;

		__sum = ((unsigned int *)__src)[0] + __carry;
		((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
		__src += 4;  
		__carry = __sum >> 32;
		if (__carry == 0) {
		    while (__src <= __srcLast4) {
			/* copy over words */
			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
			__src += 4;
		    }
		    while (__src <= __srcLast) {
			/* copy over bytes */
			__src[__ptrDelta] = __src[0];
			__src ++;
		    }
		    goto doneSource;
		}
	    }
	}
#   endif /* alpha64 */
#  endif /* i386 & WIN32 */
# endif /* i386 & GNUC */

	/*
	 * add short-wise
	 */
	while (__src < __srcLast) {
	    __carry += ((unsigned short *)__src)[0];
	    ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
	    __carry >>= 16;
	    __src += 2;
	}
	/*
	 * last (odd) byte
	 */
	if (__src <= __srcLast) {
	    __carry += __src[0];
	    __src[__ptrDelta] = __carry /* & 0xFF */;
	    __carry >>= 8;
	    __src++;
	}
#else /* not __LSBFIRST */

	/*
	 * add byte-wise
	 */
	while (__src <= __srcLast) {
	    __carry += __src[0];
	    __src[__ptrDelta] = __carry /* & 0xFF */;
	    __src++;
	    __carry >>= 8;

	    if (__carry == 0) {
		while (__src <= __srcLast) {
		    /* copy over rest */
		    __src[__ptrDelta] = __src[0];
		    __src++;
		}
		goto doneSource;
	    }
	}
#endif /* __LSBFIRST */

    doneSource: ;
	/*
	 * now, at most one other byte is to be stored ...
	 */
	if (__len < __rsltLen) {
	    __src[__ptrDelta] = __carry /* & 0xFF */;
	    __src++;
	}

	if (__src[__ptrDelta-1]) {      /* lastDigit */
	    RETURN (result);
	}
	ok = true;
    }
%}.

    ok ~~ true ifTrue:[
	index := 1.
	carry := aSmallInteger abs.

	[carry ~~ 0] whileTrue:[
	    (index <= len) ifTrue:[
		carry := (digitByteArray basicAt:index) + carry.
	    ].
	    resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
	    carry := carry bitShift:-8.
	    index := index + 1
	].

	(index <= rsltLen) ifTrue:[
	    [index <= len] whileTrue:[
		resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
		index := index + 1
	    ].
	    lastDigit := 0.
	].

	(lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
	    ^ result
	].
    ].

    ^ result compressed

    "Modified: 24.3.1997 / 21:32:41 / cg"
!

absLess:aLargeInteger
    "return true, if abs(self) < abs(theArgument).
     This handles unnormalized largeIntegers."

    |myLen "{ Class: SmallInteger }"
     otherLen "{ Class: SmallInteger }"
     d1   "{ Class: SmallInteger }"
     d2   "{ Class: SmallInteger }"
     otherDigitByteArray |

    myLen := digitByteArray size.
    otherDigitByteArray := aLargeInteger digitBytes.
    otherLen := otherDigitByteArray size.

    "/ the highest digit(s) should not be zero
    "/ when properly normalized; 
    "/ but we are tolerant here, to allow for unnormalized
    "/ numbers to be compared ...

    [myLen > 0 and:[(digitByteArray basicAt:myLen) == 0]] whileTrue:[
	myLen := myLen - 1
    ].
    [otherLen > 0 and:[(otherDigitByteArray basicAt:otherLen) == 0]] whileTrue:[
	otherLen := otherLen - 1
    ].
    (myLen < otherLen) ifTrue:[^ true].
    (myLen > otherLen) ifTrue:[^ false].

    [myLen > 0] whileTrue:[
	d1 := digitByteArray basicAt:myLen.
	d2 := otherDigitByteArray basicAt:myLen.
	d1 == d2 ifFalse:[
	    (d1 < d2) ifTrue:[^ true].
	    ^ false
	].
	myLen := myLen - 1
    ].
    ^ false

    "Modified: / 3.5.1999 / 08:06:28 / stefan"
    "Modified: / 8.5.1999 / 18:37:11 / cg"
!

absLessEq:aLargeInteger
    "return true, if abs(self) <= abs(theArgument).
     This handles unnormalized largeIntegers."

    |myLen "{ Class: SmallInteger }"
     otherLen "{ Class: SmallInteger }"
     d1   "{ Class: SmallInteger }"
     d2   "{ Class: SmallInteger }"
     otherDigitByteArray |

    myLen := digitByteArray size.
    otherDigitByteArray := aLargeInteger digitBytes.
    otherLen := otherDigitByteArray size.

    "/ the highest digit(s) should not be zero
    "/ when properly normalized; 
    "/ but we are tolerant here, to allow for unnormalized
    "/ numbers to be compared ...

    [(digitByteArray basicAt:myLen) == 0] whileTrue:[
	myLen := myLen - 1
    ].
    [(otherDigitByteArray basicAt:otherLen) == 0] whileTrue:[
	otherLen := otherLen - 1
    ].
    (myLen < otherLen) ifTrue:[^ true].
    (myLen > otherLen) ifTrue:[^ false].

    [myLen > 0] whileTrue:[
	d1 := digitByteArray basicAt:myLen.
	d2 := otherDigitByteArray basicAt:myLen.
	d1 == d2 ifFalse:[
	    (d1 < d2) ifTrue:[^ true].
	    ^ false.
	].
	myLen := myLen - 1
    ].
    ^ true

    "Created: / 13.2.1998 / 12:19:45 / stefan"
    "Modified: / 30.4.1999 / 12:46:31 / stefan"
    "Modified: / 8.5.1999 / 18:37:15 / cg"
!

absMinus:aLargeInteger sign:newSign
    "return a LargeInteger representing abs(self) - abs(theArgument)
     with sign: newSign.
     The result is normalized. The argument must be a largeInteger
     with a byteSize smaller than the receivers byteSize.
     This is a helper for addition and subtraction - not for public use."

    |result done
     otherDigitByteArray resultDigitByteArray
     len1   "{ Class: SmallInteger }"
     len2   "{ Class: SmallInteger }"
     index  "{ Class: SmallInteger }"
     borrow "{ Class: SmallInteger }"
     diff   "{ Class: SmallInteger }"
     carry  "{ Class: SmallInteger }" 
     lastDigit   
     lResult ok|

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digitBytes.
    len2 := otherDigitByteArray size.

    len1 > len2 ifTrue:[
	lResult := len1
    ] ifFalse:[
	lResult := (len1 max: len2) + 1.
    ].
    result := self class basicNew numberOfDigits:lResult.
    result sign:newSign.
    resultDigitByteArray := result digitBytes.

    lastDigit := 0.

%{
    OBJ _digitByteArray = __INST(digitByteArray);

    if (__isByteArray(_digitByteArray)
     && __isByteArray(otherDigitByteArray)
     && __isByteArray(resultDigitByteArray)) {
	int __len1 = __intVal(len1);
	int __len2 = __intVal(len2);
	int __minLen = __len1 < __len2 ? __len1 : __len2;
	int __index, __borrow = 0;
	INT __diff;
	unsigned char *__myDigits, *__otherDigits, *__resultDigits;
        
	ok = true;

	__resultDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
	__otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
	__myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;

	__index = 1;

#if defined(alpha64)
	/*
	 * subtract int-wise
	 */

	while ((__index+3) <= __minLen) {
	    /* do not make this into one expression - ask cg why */
	    __diff = ((unsigned int *)(__myDigits+__index-1))[0]; 
	    __diff -= ((unsigned int *)(__otherDigits+__index-1))[0];
	    __diff -= __borrow;

	    if (__diff >= 0) {
		__borrow = 0;
	    } else {
		__borrow = 1;
		/* __diff += 0x10000; */
	    }
	    ((unsigned int *)(__resultDigits+__index-1))[0] = __diff;
	    __index += 4;
	}
#endif /* alpha64 */

#if defined(i386) || defined(__LSBFIRST)
	/*
	 * subtract short-wise
	 */
	while (__index < __minLen) {   /* i.e. index+1 <= minLen */
	    /* do not make this into one expression - ask cg why */
	    __diff = ((unsigned short *)(__myDigits+__index-1))[0];
	    __diff -= ((unsigned short *)(__otherDigits+__index-1))[0];
	    __diff -= __borrow;
	    if (__diff >= 0) {
		__borrow = 0;
	    } else {
		__borrow = 1;
		/* __diff += 0x10000; */
	    }
	    ((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
	    __index += 2;
	}

	if (__index == __minLen) {
	    /* one of the operands has odd length - cannot continue short-wise */
	} else {
	    if (__len1 > __len2) {
		while (__index < __len1) {
		    /* do not make this into one expression - ask cg why */
		    __diff = ((unsigned short *)(__myDigits+__index-1))[0];
		    __diff -= __borrow;
		    if (__diff >= 0) {
			__borrow = 0;
			((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
			__index += 2;

			/* copy over rest */
			while (__index < __len1) {
			    ((unsigned short *)(__resultDigits+__index-1))[0] = ((unsigned short *)(__myDigits+__index-1))[0];
			    __index+=2;
			}
			if (__index <= __len1) {
			    __resultDigits[__index-1] = __myDigits[__index-1];
			    __index++;
			}
			break;
		    }
		    __borrow = 1;
		    /* __diff += 0x10000; */
		    ((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
		    __index += 2;
		}
	    } else {
		if (__len2 > __len1) {
		    while (__index < __len2) {
			/* do not make this into one expression - ask cg why */
			__diff = 0;
			__diff -= ((unsigned short *)(__otherDigits+__index-1))[0];
			__diff -= __borrow;
			if (__diff >= 0) {
			    __borrow = 0;
			} else {
			    __borrow = 1;
			    /* __diff += 0x10000; */
			}
			((unsigned short *)(__resultDigits+__index-1))[0] = __diff;
			__index += 2;
		    }
		}
	    }
	}
#endif
	/*
	 * subtract byte-wise
	 */
	while (__index <= __minLen) {
	    /* do not make this into one expression - ask cg why */
	    __diff = __myDigits[__index-1];
	    __diff -= __otherDigits[__index-1];
	    __diff -= __borrow;
	    if (__diff >= 0) {
		__borrow = 0;
	    } else {
		__borrow = 1;
		/* __diff += 0x100; */
	    }
	    __resultDigits[__index-1] = __diff;
	    __index++;
	}

	if (__len1 > __len2) {
	    while (__index <= __len1) {
		/* do not make this into one expression - ask cg why */
		__diff = __myDigits[__index-1];
		__diff -= __borrow;
		if (__diff >= 0) {
		    __borrow = 0;
		    /* copy over rest */
		    __resultDigits[__index-1] = __diff;
		    __index++;
		    while (__index <= __len1) {
			__resultDigits[__index-1] = __myDigits[__index-1];
			__index++;
		    }
		    break;
		}
		__borrow = 1;
		/* __diff += 0x100; */
		__resultDigits[__index-1] = __diff;
		__index++;
	    }
	} else {
	    if (__len2 > __len1) {
		while (__index <= __len2) {
		    /* do not make this into one expression - ask cg why */
		    __diff = 0;
		    __diff -= __otherDigits[__index-1];
		    __diff -= __borrow;
		    if (__diff >= 0) {
			__borrow = 0;
		    } else {
			__borrow = 1;
			/* __diff += 0x100; */
		    }
		    __resultDigits[__index-1] = __diff;
		    __index++;
		}
	    }
	}
	borrow = __MKSMALLINT(__borrow);
	index = __MKSMALLINT(__index);
	lastDigit = __MKSMALLINT(__resultDigits[__intVal(lResult)-1]);
    }
%}.
    ok == true ifFalse:[
	index := 1.
	borrow := 0.

	done := false.
	[done] whileFalse:[
	    diff := borrow.
	    (index <= len1) ifTrue:[
		diff := diff + (digitByteArray basicAt:index).
		(index <= len2) ifTrue:[
		    diff := diff - (otherDigitByteArray basicAt:index)
		]
	    ] ifFalse:[
		(index <= len2) ifTrue:[
		    diff := diff - (otherDigitByteArray basicAt:index)
		] ifFalse:[
		    "end reached"
		    done := true
		]
	    ].

	    "/ workaround for
	    "/ gcc code generator bug

	    (diff >= 0) ifTrue:[
		borrow := 0
	    ] ifFalse:[
		borrow := -1.
		diff := diff + 16r100
	    ].

    "/        (diff < 0) ifTrue:[
    "/            borrow := -1.
    "/            diff := diff + 16r100
    "/        ] ifFalse:[
    "/            borrow := 0
    "/        ].

	    resultDigitByteArray basicAt:index put:diff.
	    index := index + 1
	].
	lastDigit := resultDigitByteArray basicAt:lResult.
    ].

    (borrow ~~ 0) ifTrue:[
	"/ must generate 255's complement

	result sign:-1.
	[index <= lResult] whileTrue:[
	    resultDigitByteArray basicAt:index put:16rFF.
	    index := index + 1.
	].
	index := lResult.
	[index > 0] whileTrue:[
	    resultDigitByteArray basicAt:index put:(255 - (resultDigitByteArray at:index)).
	    index := index - 1.
	].

	index := 1.
	carry := 1.
	[carry ~~ 0] whileTrue:[
	    (index <= lResult) ifTrue:[
		carry := (resultDigitByteArray basicAt:index) + carry.
	    ].
	    resultDigitByteArray basicAt:index put:(carry bitAnd:16rFF).
	    carry := carry bitShift:-8.
	    index := index + 1
	].
	lastDigit := resultDigitByteArray basicAt:lResult.
    ].
    (lastDigit ~~ 0 and:[lResult > SmallInteger maxBytes]) ifTrue:[
	^ result
    ].
    ^ result compressed

    "Modified: 5.11.1996 / 14:09:25 / cg"
!

absMod:anInteger
    "return a LargeIntegers representing
     abs(self) \\ abs(theArgument).
     Used as a helper for \\ and rem:"


    |dividend divisor 
     shift "{ Class: SmallInteger }" |

    anInteger == 0 ifTrue:[
        ^ ZeroDivide raiseRequestWith:thisContext
    ].

    self = anInteger ifTrue:[
        ^ 0
    ].

    shift := self highBit - anInteger highBit.
    dividend := LargeInteger digitBytes:digitByteArray copy. "/ self simpleDeepCopy sign:1.
    shift < 0 ifTrue:[
        ^ dividend compressed.
    ].
    shift == 0 ifTrue:[
        divisor := LargeInteger digitBytes:(anInteger digitBytes copy). "/ anInteger simpleDeepCopy
    ] ifFalse:[
        divisor := anInteger bitShift:shift.
    ].


    shift := shift + 1.
    [shift > 0] whileTrue:[
        (dividend absLess:divisor) ifFalse:[
            (dividend absSubtract: divisor) ifFalse:[ "result == 0"
                ^ dividend compressed            
            ].
        ].
        shift := shift - 1.
        divisor div2.
    ].

    ^ dividend compressed

    "
Time millisecondsToRun:[   10000 timesRepeat:[  16000000001 absMod:4000000001] ]  
Time millisecondsToRun:[   10000 timesRepeat:[  16000000001 absDivMod:4000000001] ]  
     16000000000 absMod:4000000000
     16000000000 absMod:3000000000
    "

    "Modified: / 5.11.1996 / 18:40:24 / cg"
    "Created: / 27.4.1999 / 19:45:44 / stefan"
    "Modified: / 26.7.1999 / 10:46:18 / stefan"
!

absMul:aLargeInteger
    "return a LargeInteger representing abs(self) * abs(theArgument)"

    |result otherDigitByteArray resultDigitByteArray ok
     idx      "{ Class: SmallInteger }"
     carry    "{ Class: SmallInteger }"
     len1     "{ Class: SmallInteger }"
     len2     "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     prod     "{ Class: SmallInteger }"
     v        "{ Class: SmallInteger }"|

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digitBytes.
    len2 := otherDigitByteArray size.

    result := LargeInteger basicNew numberOfDigits:(len1 + len2).
    resultDigitByteArray := result digitBytes.
    ok := false.
%{
    if (__isByteArray(__INST(digitByteArray))
     && __isByteArray(otherDigitByteArray)
     && __isByteArray(resultDigitByteArray)
     && __bothSmallInteger(len1, len2)) {
        unsigned char *myBytes = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
        unsigned char *otherBytes = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
        unsigned char *resultBytes = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
        unsigned char *_p1, *_p2, *_pResult, *_pResult0, *_pResult1, *_p1Last, *_p2Last;
        unsigned char *_pResultLast1;
        unsigned INT _v;
        int _len1 = __intVal(len1);
        int _len2 = __intVal(len2);

        _p1Last = myBytes    + _len1 - 1;  /* the last byte */
        _p2Last = otherBytes + _len2 - 1;  /* the last byte */
        _pResult0 = resultBytes;

        /*
         *        aaa...aaa      f1[0] * f2
         *       bbb...bbb       f1[1] * f2
         *      ccc...ccc        f1[2] * f2
         *     ...
         *    xxx...xxx          f1[high] * f2
         *
         * start short-wise
         * bounds: (16rFFFF * 16rFFFF) + 16rFFFF -> FFFF0000
         */
        _p1 = myBytes;

#if defined(alpha64)
        /* loop over ints of f1 */
        for (; _p1 < _p1Last-2; _p1 += 4, _pResult0 += 4) {
            unsigned INT word1 = ((unsigned int *)_p1)[0];

            _pResult = _pResult0;
            _p2 = otherBytes;

            /* loop over ints of f2 */
            while (_p2 < (_p2Last-2)) {
                _v = (word1 * ((unsigned int *)_p2)[0]) + ((unsigned int *)_pResult)[0];
                ((unsigned int *)_pResult)[0] = _v /* & 0xFFFFFFFF */;
                _v >>= 32; /* now _v contains the carry*/
                _pResult += 4;                
                if (_v) {
                    unsigned char *_pResultLast3;

                    /* distribute carry - int-wise, then byte-wise */
                    _pResultLast3 = _pResult0 + _len1 + _len2 - 1 - 3;
                    for (_pResult1 = _pResult; _v; _pResult1 += 4) {
                        if (_pResult1 > _pResultLast3) break;
                        _v += ((unsigned int *)_pResult1)[0];
                        ((unsigned int *)_pResult1)[0] = _v /* & 0xFFFFFFFF */;
                        _v >>= 32;
                    }
                    for (; _v; _pResult1++) {
                        _v += _pResult1[0];
                        _pResult1[0] = _v /* & 0xFF */;
                        _v >>= 8;
                    }
                }
                _p2 += 4;
            }

            /* possible odd highByte of f2 */
            while (_p2 <= _p2Last) {
                _v = (word1 * _p2[0]) + ((unsigned int *)_pResult)[0];
                ((unsigned int *)_pResult)[0] = _v /* & 0xFFFFFFFF */;
                _v >>= 32; /* now _v contains the carry*/
                _pResult += 4;                
                if (_v) {
                    unsigned char *_pResultLast3;

                    /* distribute carry - int-wise, then byte-wise */
                    _pResultLast3 = _pResult0 + _len1 + _len2 - 1 - 3;
                    for (_pResult1 = _pResult; _v; _pResult1 += 4) {
                        if (_pResult1 > _pResultLast3) break;
                        _v += ((unsigned int *)_pResult1)[0];
                        ((unsigned int *)_pResult1)[0] = _v /* & 0xFFFFFFFF */;
                        _v >>= 32;
                    }
                    for (; _v; _pResult1++) {
                        _v += _pResult1[0];
                        _pResult1[0] = _v /* & 0xFF */;
                        _v >>= 8;
                    }
                }
                _p2++;
            }
        }
#endif /* alpha64 */

        /* loop over shorts of f1 */
        for (; _p1 < _p1Last; _p1 += 2, _pResult0 += 2) {
            unsigned int short1 = ((unsigned short *)_p1)[0];

#if !defined(__LSBFIRST) && !defined(alpha) && !defined(i386)  
            short1 = ((short1 >> 8) & 0xFF) | ((short1 & 0xFF) << 8);
#endif
            _pResult = _pResult0;
            _p2 = otherBytes;

            /* loop over shorts of f2 */
            while (_p2 < _p2Last) {
#if !defined(__LSBFIRST) && !defined(alpha) && !defined(i386)  
                unsigned int _short2;
                unsigned int _short3;

                _short2 = ((unsigned short *)_p2)[0];
                _short2 = ((_short2 >> 8) /* & 0xFF */) | ((_short2 & 0xFF) << 8);
                _short3 = ((unsigned short *)_pResult)[0];
                _short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
                _v = (short1 * _short2) + _short3;
                _pResult[0] = _v;
                _pResult[1] = _v >> 8;
#else /* LSBFIRST */
                _v = (short1 * ((unsigned short *)_p2)[0]) + ((unsigned short *)_pResult)[0];
                ((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
#endif
                _v >>= 16; /* now _v contains the carry*/
                _pResult += 2;                
                if (_v) {
                    /* distribute carry - short-wise, then byte-wise */
                    _pResult1 = _pResult;
#if defined(__LSBFIRST) || defined(alpha) || defined(i386)  
                    _pResultLast1 = _pResult0 + _len1 + _len2 - 1 - 1;
                    for (; _v; _pResult1 += 2) {
                        if (_pResult1 > _pResultLast1) break;
                        _v += ((unsigned short *)_pResult1)[0];
                        ((unsigned short *)_pResult1)[0] = _v /* & 0xFFFF */;
                        _v >>= 16;
                    }
#endif
                    for (; _v; _pResult1++) {
                        _v += _pResult1[0];
                        _pResult1[0] = _v /* & 0xFF */;
                        _v >>= 8;
                    }
                }
                _p2 += 2;
            }

            /* possible odd highByte of f2 */
            if (_p2 <= _p2Last) {
#if !defined(__LSBFIRST) && !defined(alpha) && !defined(i386)  
                unsigned int _short3;

                _short3 = ((unsigned short *)_pResult)[0];
                _short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
                _v = (short1 * _p2[0]) + _short3;
                _pResult[0] = _v;
                _pResult[1] = _v >> 8;
#else /* LSBFIRST */
                _v = (short1 * _p2[0]) + ((unsigned short *)_pResult)[0];
                ((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
#endif
                _v >>= 16; /* now _v contains the carry*/
                _pResult += 2;                
                if (_v) {
                    /* distribute carry - short-wise, then byte-wise */
                    _pResult1 = _pResult;
#if defined(__LSBFIRST) || defined(alpha) || defined(i386)  
                    _pResultLast1 = _pResult0 + _len1 + _len2 - 1 - 1;
                    for (; _v; _pResult1 += 2) {
                        if (_pResult1 > _pResultLast1) break;
                        _v += ((unsigned short *)_pResult1)[0];
                        ((unsigned short *)_pResult1)[0] = _v /* & 0xFFFF */;
                        _v >>= 16;
                    }
#endif
                    for (; _v; _pResult1++) {
                        _v += _pResult1[0];
                        _pResult1[0] = _v /* & 0xFF */;
                        _v >>= 8;
                    }
                }
                _p2++;
            }
        }

        /* possible odd highByte of f1 (or byteLoop, if not LSBFIRST) */
        for (; _p1 <= _p1Last; _p1++, _pResult0++) {
            unsigned int byte1 = _p1[0];

            _pResult = _pResult0;
            _p2 = otherBytes;

            /* loop over shorts of f2 */
            while (_p2 < _p2Last) {
#if !defined(__LSBFIRST) && !defined(alpha) && !defined(i386)  
                unsigned int _short2;
                unsigned int _short3;

                _short2 = ((unsigned short *)_p2)[0];
                _short2 = ((_short2 >> 8) /* & 0xFF */) | ((_short2 & 0xFF) << 8);
                _short3 = ((unsigned short *)_pResult)[0];
                _short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
                _v = (byte1 * _short2) + _short3;
                _pResult[0] = _v;
                _pResult[1] = _v >> 8;
#else /* LSBFIRST */
                _v = (byte1 * ((unsigned short *)_p2)[0]) + ((unsigned short *)_pResult)[0];
                ((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
#endif
                _v >>= 16; /* now _v contains the carry*/
                _pResult += 2;                
                if (_v) {
                    /* distribute carry - short-wise, then byte-wise */
                    _pResult1 = _pResult;
#if defined(__LSBFIRST) || defined(alpha) || defined(i386)
                    _pResultLast1 = _pResult0 + _len1 + _len2 - 1 - 1;
                    for (_pResult1 = _pResult; _v; _pResult1 += 2) {
                        if (_pResult1 > _pResultLast1) break;
                        _v += ((unsigned short *)_pResult1)[0];
                        ((unsigned short *)_pResult1)[0] = _v /* & 0xFFFF */;
                        _v >>= 16;
                    }
#endif /* __LSBFIRST */
                    for (; _v; _pResult1++) {
                        _v += _pResult1[0];
                        _pResult1[0] = _v /* & 0xFF */;
                        _v >>= 8;
                    }
                }
                _p2 += 2;
            }

            /* possible odd highByte of f2 (or byteLoop, if not LSBFIRST) */
            while (_p2 <= _p2Last) {
                _v = (byte1 * _p2[0]) + _pResult[0];
                _pResult[0] = _v /* & 0xFF */;
                _v >>= 8; /* now _v contains the carry*/
                _pResult++;                
                if (_v) {
                    /* distribute carry */
                    for (_pResult1 = _pResult; _v; _pResult1++) {
                        _v += _pResult1[0];
                        _pResult1[0] = _v /* & 0xFF */;
                        _v >>= 8;
                    }
                }
                _p2++;
            }
        }
        ok = true;
    }
%}.
    ok ifFalse:[
        1 to:len1 do:[:index1 |
            1 to:len2 do:[:index2 |
                dstIndex := index1 + index2 - 1.
                prod := (digitByteArray basicAt:index1) * (otherDigitByteArray basicAt:index2).
                prod := prod + (resultDigitByteArray basicAt:dstIndex).
                resultDigitByteArray basicAt:dstIndex put:(prod bitAnd:16rFF).
                carry := prod bitShift:-8.
                carry ~~ 0 ifTrue:[
                    idx := dstIndex + 1.
                    [carry ~~ 0] whileTrue:[
                        v := (resultDigitByteArray basicAt:idx) + carry.
                        resultDigitByteArray basicAt:idx put:(v bitAnd:255).
                        carry := v bitShift:-8.
                        idx := idx + 1
                    ]
                ]
            ]
        ].
    ].
    ^ result compressed
!

absPlus:aLargeInteger sign:newSign
    "return a LargeInteger representing abs(self) + abs(theArgument)
     with sign: newSign.
     The result is normalized. The argument must be a smallInteger
     with byteSize one less than the integer byteSize.
     This is a helper for addition and subtraction - not for public use."

    |result done otherDigitByteArray resultDigitByteArray
     len1   "{ Class: SmallInteger }"
     len2   "{ Class: SmallInteger }"
     newLen "{ Class: SmallInteger }"
     index  "{ Class: SmallInteger }"
     carry  "{ Class: SmallInteger }"
     sum    "{ Class: SmallInteger }" |

    otherDigitByteArray := aLargeInteger digitBytes.

%{
    OBJ _digitByteArray = __INST(digitByteArray);

    if (__isByteArray(_digitByteArray)
     && __isByteArray(otherDigitByteArray)) {
	int _len1, _len2, _newLen;
	unsigned char *_myDigits, *_otherDigits, *_newDigits;
	int _index, _carry;
	int _comLen;

	_len1 = __byteArraySize(_digitByteArray);
	_len2 = __byteArraySize(otherDigitByteArray);

	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;

	if (_len1 < _len2) {
	    _comLen = _len1;
	    _newLen = _len2;
	    if (_otherDigits[_len2 - 1] == 0xFF) _newLen++;
	} else if (_len2 < _len1) {
	    _comLen = _len2;
	    _newLen = _len1;
	    if (_myDigits[_len1 - 1] == 0xFF) _newLen++;
	} else {
	    /*
	     * there can only be an overflow from the high bytes,
	     * if their sum is >= 255
	     * (with sum==255, a carry could still occur from the next lower bytes)
	     */
	    _newLen = _len1;
	    if ((_otherDigits[_len2 - 1] + _myDigits[_len1 - 1]) >= 0xFF) {
		_newLen++;
	    } else {
		if (_newLen == sizeof(INT)) {
		    OBJ _uint;

		    /* 
		     * two word-sized numbers, no carry - a very common case ...
		     */
#if defined(__LSB_FIRST) || defined(i386) || defined(alpha)
		    unsigned INT _sum = *(unsigned INT *)_otherDigits + *(unsigned INT *)_myDigits;
#else
		    unsigned INT _sum = __unsignedLongIntVal(self) + __unsignedLongIntVal(aLargeInteger);
#endif /* not LSB_FIRST */
		    if (_sum <= _MAX_INT) {
			_uint = __MKSMALLINT(_sum * __intVal(newSign));
		    } else {
			_uint = __MKULARGEINT(_sum);
			__LargeIntegerInstPtr(_uint)->l_sign = newSign;
		    }
		    RETURN (_uint);
		}
	    }
	    _comLen = _len1;
	}
	resultDigitByteArray = __BYTEARRAY_UNINITIALIZED_NEW_INT(_newLen);

	/*
	 * must refetch - GC could have been invoked
	 */
	_digitByteArray = __INST(digitByteArray);

	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
	_newDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;

	/*
	 * add them ...
	 */
	_index = 1;
	_carry = 0;

#if defined(__LSBFIRST) || defined(alpha) || defined(i386)
# if 0 && defined(alpha64) && defined(__GNUC__)
	{
	    int _comLen7;

	    /*
	     * have a 64bit integers;
	     * add quad-wise
	     * accessing bytes at: [index-1][index][index+1]..[index+6]
	     */
	    _comLen7 = _comLen - 3 - 4;
	    while (_index <= _comLen7) {
		UINT64 _sum, _t1, _t2;

		asm ("addq   %5,%6,%1         /* sum */                  \n\
		      addq   %0,%1,%1         /* plus carryIn */         \n\
		      cmpult %1,%5,%2         /* was there a carry ? */  \n\
		      cmpult %1,%6,%3         /* was there a carry ? */  \n\
		      bis    %2,%3,%0         /* carryOut */             \n\
		     "    
			: "=r"  (_carry),
			  "=r"  (_sum),
			  "r"   (_t1),
			  "r"   (_t2)
			: "r"   (_carry),
			  "r"   (((unsigned long *)(&(_myDigits[_index - 1])))[0]), 
			  "r"   (((unsigned long *)(&(_otherDigits[_index - 1])))[0])
		    );
		/* _sum = _sum & 0xFFFFFFFF; */
		((unsigned long *)(&(_newDigits[_index - 1])))[0] = _sum;
		_index += 8;
	    }
	}
# endif /* alpha64 */

# if 0 && defined(alpha64)      /* not faster */
	{
	    int _comLen7;

	    /*
	     * have a 64bit integers;
	     * add quad-wise
	     * accessing bytes at: [index-1][index][index+1]..[index+6]
	     */
	    _comLen7 = _comLen - 3 - 4;
	    while (_index <= _comLen7) {
		UINT64 _sum, _t1, _t2;

		_t1 = ((UINT64 *)(&(_myDigits[_index - 1])))[0];
		_t2 = ((UINT64 *)(&(_otherDigits[_index - 1])))[0];
		_sum = _t1 + _t2 + _carry;
		((UINT64 *)(&(_newDigits[_index - 1])))[0] = _sum;
		_carry = (_sum < _t1) | (_sum < _t2);
		_index += 8;
	    }
	}
# endif /* alpha64 */

# ifdef UINT64
	{
	    int _comLen3;

	    /*
	     * have a 64bit integer type;
	     * add int-wise
	     * accessing bytes at: [index-1][index][index+1][index+2]
	     */
	    _comLen3 = _comLen - 3;
	    while (_index <= _comLen3) {
		UINT64 _sum;

		/* do not merge the 3 lines below into one -
		 * (will do sign extension then, which is wrong here)
		 */
		_sum = (unsigned)_carry;
		_sum += ((unsigned int *)(&(_myDigits[_index - 1])))[0];
		_sum += ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
		_carry = _sum >> 32;
		/* _sum = _sum & 0xFFFFFFFF; */
		((unsigned int *)(&(_newDigits[_index - 1])))[0] = _sum;
		_index += 4;
	    }
	}
# else
#  if defined(i386) && defined(__GNUC__)
	{
	    int _comLen3;

	    _comLen3 = _comLen - 3 - 4;
	    while (_index <= _comLen3) {
		unsigned int _sum, _sum2;
		unsigned int __in1A, __in1B, __in2A, __in2B;

		__in1A = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
		__in2A = ((unsigned int *)(&(_myDigits[_index - 1])))[1];
		__in1B = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
		__in2B = ((unsigned int *)(&(_otherDigits[_index - 1])))[1];

		asm ("addl %%edx,%%eax  \n\
		      movl $0,%%edx     \n\
		      adcl $0,%%edx     \n\
		      addl %5,%%eax     \n\
		      adcl $0,%%edx     \n\
					\n\
		      addl %%edx,%%ecx  \n\
		      movl $0,%%edx     \n\
		      adcl $0,%%edx     \n\
		      addl %7,%%ecx     \n\
		      adcl $0,%%edx     \n\
		     "    
			: "=d"  (_carry),
			  "=a"  (_sum),
			  "=c"  (_sum2)
			: "0"   (_carry),
			  "1"   (__in1A), 
			  "rm"  (__in1B), 
			  "2"   (__in2A), 
			  "rm"  (__in2B) 
		    );

		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
		((unsigned *)(&(_newDigits[_index - 1])))[1] = _sum2;
		_index += 8;
	    }
	    /*
	     * add int-wise
	     * accessing bytes at: [index-1][index][index+1][index+2]
	     */
	    _comLen3 = _comLen3 + 4;
	    if (_index <= _comLen3) {
		unsigned int _sum;
		unsigned int __inA, __inB;

		__inA = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
		__inB = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];

		asm ("addl %%edx,%%eax      \n\
		      movl $0,%%edx         \n\
		      adcl $0,%%edx         \n\
		      addl %4,%%eax         \n\
		      adcl $0,%%edx"    
			: "=d"  (_carry),
			  "=a"  (_sum)
			: "0"   (_carry),
			  "1"   (__inA), 
			  "rm"  (__inB) 
		    );

		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
		_index += 4;
	    }
	}
#  endif /* i386 && GNUC */
#  if defined(i386) && defined(WIN32)
	{
	    int _comLen3;

	    /*
	     * add long-wise
	     * accessing bytes at: [index-1][index][index+1][index+2]
	     */
	    _comLen3 = _comLen - 3;
	    while (_index <= _comLen3) {
		unsigned int _sum, _v1, _v2;

		_v1 = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
		_v2 = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
		asm { 
		      mov eax, _v1   
		      add eax, _v2   
		      mov edx, 0
		      adc edx, 0
		      add eax, _carry   
		      adc edx, 0
		      mov _carry, edx
		      mov _sum, eax
		    }

		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
		_index += 4;
	    }
	}
#  endif /* i386 && WIN32 */
# endif /* INT64 */
	/*
	 * add short-wise
	 * accessing bytes at: [index-1][index]
	 */
	while (_index < _comLen) {
	    unsigned int _sum;

	    _sum = _carry 
		   + ((unsigned short *)(&(_myDigits[_index - 1])))[0]
		   + ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
	    _carry = _sum >> 16;
	    /* _sum = _sum & 0xFFFF; */
	    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
	    _index += 2;
	}
#else
# ifdef sparc
	/*
	 * add short-wise
	 * accessing bytes at: [index-1][index]
	 */
	while (_index < _comLen) {
	    unsigned int _sum;
	    unsigned short _v1, _v2;

	    _v1 = ((unsigned short *)(&(_myDigits[_index - 1])))[0];
	    _v2 = ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
	    _sum = _carry + (_v1>>8) + (_v2>>8);
	    _carry = _sum >> 8;
	    _newDigits[_index - 1] = _sum;

	    _sum = _carry + (_v1 & 0xFF) + (_v2 & 0xFF);
	    _carry = _sum >> 8;
	    _newDigits[_index] = _sum;
	    _index += 2;
	}
# endif
#endif /* __LSBFIRST */

	/*
	 * add byte-wise
	 */
	while (_index <= _comLen) {
	    unsigned int _sum;

	    _sum = _carry 
		   + _myDigits[_index - 1] 
		   + _otherDigits[_index - 1];
	    _carry = _sum >> 8;
	    /* _sum = _sum & 0xFF; */
	    _newDigits[_index - 1] = _sum;
	    _index++;
	}

	/*
	 * rest
	 */
	if (_len1 > _len2) {
#if defined(__LSBFIRST) || defined(alpha) || defined(i386)
	    if (_index <= _len1) {
		if ((_index - 1) & 1) {
		    /* odd byte */
		    unsigned int _sum;

		    _sum = _carry + _myDigits[_index - 1];
		    _carry = _sum >> 8;
		    /* _sum = _sum & 0xFF; */
		    _newDigits[_index - 1] = _sum;
		    _index++;
		}

		while (_index < _len1) {
		    /* shorts */
		    unsigned int _sum;

		    _sum = _carry + *(unsigned short *)(&(_myDigits[_index - 1]));
		    _carry = _sum >> 16;
		    /* _sum = _sum & 0xFFFF; */
		    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
		    _index += 2;
		}

		if (_index <= _len1) {
		    /* last byte */
		    unsigned int _sum;

		    _sum = _carry + _myDigits[_index - 1];
		    _carry = _sum >> 8;
		    /* _sum = _sum & 0xFF; */
		    _newDigits[_index - 1] = _sum;
		    _index++;
		}
	    }
#else
	    while (_index <= _len1) {
		unsigned int _sum;

		_sum = _carry + _myDigits[_index - 1];
		_carry = _sum >> 8;
		/* _sum = _sum & 0xFF; */
		_newDigits[_index - 1] = _sum;
		_index++;
	    }
#endif /* not LSB */
	} else {
	    if (_len2 > _len1) {
#if defined(__LSBFIRST) || defined(alpha) || defined(i386)
		if (_index <= _len2) {
		    if ((_index - 1) & 1) {
			/* odd byte */
			unsigned int _sum;

			_sum = _carry + _otherDigits[_index - 1];
			_carry = _sum >> 8;
			/* _sum = _sum & 0xFF; */
			_newDigits[_index - 1] = _sum;
			_index++;
		    }

		    while (_index < _len2) {
			/* shorts */
			unsigned int _sum;

			_sum = _carry + *(unsigned short *)(&(_otherDigits[_index - 1]));
			_carry = _sum >> 16;
			/* _sum = _sum & 0xFFFF; */
			*(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
			_index += 2;
		    }

		    if (_index <= _len2) {
			/* last byte */
			unsigned int _sum;

			_sum = _carry + _otherDigits[_index - 1];
			_carry = _sum >> 8;
			/* _sum = _sum & 0xFF; */
			_newDigits[_index - 1] = _sum;
			_index++;
		    }
		}
#else
		while (_index <= _len2) {
		    unsigned int _sum;

		    _sum = _carry + _otherDigits[_index - 1];
		    _carry = _sum >> 8;
		    /* _sum = _sum & 0xFF; */
		    _newDigits[_index - 1] = _sum;
		    _index++;
		}
#endif /* not LSB */
	    }
	}

	while (_index <= _newLen) {
	    unsigned int _sum;

	    _sum = _carry;
	    _carry = _sum >> 8;
	    /* _sum = _sum & 0xFF; */
	    _newDigits[_index - 1] = _sum;
	    _index++;
	}
    }
%}.
    resultDigitByteArray notNil ifTrue:[
	result := self class basicNew.
	result setDigits:resultDigitByteArray.
	result sign:newSign.
    ] ifFalse:[
	len1 := digitByteArray size.
	len2 := otherDigitByteArray size.

	"/ earlier versions estimated the newLength as:
	"/ (len1 max:len2) + 1
	"/ and reduced the result.
	"/ however, if one of the addends is smaller,
	"/ the result will never require another digit,
	"/ if the highest digit of the larger addent is
	"/ not equal to 255. Therefore, in most cases,
	"/ we can avoid the computation and resizing 
	"/ in #reduced.

	len1 < len2 ifTrue:[
	    newLen := len2.
	    (otherDigitByteArray at:len2) == 16rFF ifTrue:[
		newLen := newLen + 1
	    ]
	] ifFalse:[
	    len2 < len1 ifTrue:[
		newLen := len1.
		(digitByteArray at:len1) == 16rFF ifTrue:[
		    newLen := newLen + 1
		]
	    ] ifFalse:[
		newLen := len1 + 1.
	    ]
	].

	result := self class basicNew numberOfDigits:newLen.
	result sign:newSign.
	resultDigitByteArray := result digitBytes.

	index := 1.
	carry := 0.

	done := false.
	[done] whileFalse:[
	    sum := carry.
	    (index <= len1) ifTrue:[
		sum := sum + (digitByteArray basicAt:index).
		(index <= len2) ifTrue:[
		    sum := sum + (otherDigitByteArray basicAt:index)
		]
	    ] ifFalse:[
		(index <= len2) ifTrue:[
		    sum := sum + (otherDigitByteArray basicAt:index)
		] ifFalse:[
		    "end reached"
		    done := true
		]
	    ].
	    (sum >= 16r100) ifTrue:[
		carry := 1.
		sum := sum - 16r100
	    ] ifFalse:[
		carry := 0
	    ].
	    resultDigitByteArray basicAt:index put:sum.
	    index := index + 1
	].
    ].

    ^ result compressed

    "Modified: 11.8.1997 / 03:23:37 / cg"
!

absSubtract:aLargeInteger
    "private helper for division:
        destructively subtract aLargeInteger from myself
        AND return true, if the result is non-zero, false otherwise.
        (i.e. this method has both a return value and a side-effect
         on the receiver)
        Only allowed for positive receiver and argument
        The receiver must be >= the argument.
        The receiver must be a temporary scratch-number"

    |otherDigitByteArray
     len1   "{ Class: SmallInteger }"
     len2   "{ Class: SmallInteger }"
     index  "{ Class: SmallInteger }"
     borrow "{ Class: SmallInteger }"
     diff   "{ Class: SmallInteger }"
     notZero
    |

    notZero := false.
    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digitBytes.
    len2 := otherDigitByteArray size.
    len2 > len1 ifTrue:[
        [(otherDigitByteArray at:len2) == 0] whileTrue:[
            len2 := len2 - 1
        ].
        len2 > len1 ifTrue:[
            self error:'operation failed' "/ may not be called that way
        ].
    ].
    "/ knowing that len2 is <= len1
%{

    OBJ _digitByteArray = __INST(digitByteArray);

    if (__isByteArray(_digitByteArray)
     && __isByteArray(otherDigitByteArray)) {
        int _len1 = __intVal(len1), 
            _len2 = __intVal(len2);
        unsigned char *_myDigits, *_otherDigits;
        int _index = 1, _borrow = 0;
        INT _diff;
        INT anyBitNonZero = 0;

        _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
        _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;

#if defined(alpha64)
        {
            int _len2Q;
            /*
             * subtract int-wise
             */
            _len2Q = _len2-2;
            while (_index < _len2Q) {
                /* do not combine the expression below (may lead to unsigned result on some machines */
                _diff = ((unsigned int *)(_myDigits+_index-1))[0];
                _diff -= ((unsigned int *)(_otherDigits+_index-1))[0];
                _diff -= _borrow;
                if (_diff >= 0) {
                    _borrow = 0;
                } else {
                    _borrow = 1;
                    /* _diff += 0x10000; */
                }
                ((unsigned int *)(_myDigits+_index-1))[0] = _diff;
                anyBitNonZero |= (_diff & 0xFFFFFFFFL);
                _index += 4;
            }
        }
#endif

#if defined(i386) || defined(__LSBFIRST)
        /*
         * subtract short-wise
         */
        while (_index < _len2) {
            /* do not combine the expression below (may lead to unsigned result on some machines */
            _diff = ((unsigned short *)(_myDigits+_index-1))[0];
            _diff -= ((unsigned short *)(_otherDigits+_index-1))[0];
            _diff -= _borrow;
            if (_diff >= 0) {
                _borrow = 0;
            } else {
                _borrow = 1;
                /* _diff += 0x10000; */
            }
            ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
            anyBitNonZero |= (_diff & 0xFFFF);
            _index += 2;
        }

        if (_index <= _len2) {
            /*
             * cannot continue with shorts - there is an odd number of
             * bytes in the minuent
             */
        } else {
            while (_index < _len1) {
                /* do not combine the expression below (may lead to unsigned result on some machines */
                _diff = ((unsigned short *)(_myDigits+_index-1))[0];
                _diff -= _borrow;
                if (_diff >= 0) {
                    /* _borrow = 0; */
                    ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
                    anyBitNonZero |= (_diff & 0xFFFF);
                    _index += 2;
                    while (_index < _len1) {
                        anyBitNonZero |= ((unsigned short *)(_myDigits+_index-1))[0];
                        if (anyBitNonZero) {
                            RETURN (true);
                        }
                        _index += 2;
                    }
                    /* last odd index */
                    if (_index <= _len1) {
                        anyBitNonZero |= _myDigits[_index - 1];;
                        if (anyBitNonZero) {
                            RETURN (true);
                        }
                        _index++;
                    }
                    RETURN (anyBitNonZero ? true : false);
                }
                _borrow = 1;
                /* _diff += 0x10000; */

                ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
                anyBitNonZero |= (_diff & 0xFFFF);
                _index += 2;
            }
        }
#endif
        /*
         * subtract byte-wise
         */
        while (_index <= _len2) {
            /* do not combine the expression below (may lead to unsigned result on some machines */
            _diff = _myDigits[_index - 1];
            _diff -= _otherDigits[_index - 1];
            _diff -= _borrow;
            if (_diff >= 0) {
                _borrow = 0;
            } else {
                _borrow = 1;
                /* _diff += 0x100; */
            }
            _myDigits[_index - 1] = _diff;
            anyBitNonZero |= (_diff & 0xFF);
            _index++;
        }

        while (_index <= _len1) {
            /* do not combine the expression below (may lead to unsigned result on some machines */
            _diff = _myDigits[_index - 1];
            _diff -= _borrow;
            if (_diff >= 0) {
                /* _borrow = 0; */
                _myDigits[_index - 1] = _diff;
                anyBitNonZero |= (_diff & 0xFF);
                _index++;
                while (_index <= _len1) {
                    anyBitNonZero |= _myDigits[_index - 1];
                    if (anyBitNonZero) {
                        RETURN (true);
                    }
                    _index++;
                }
                break;
            }
            _borrow = 1;
            /* _diff += 0x100; */

            _myDigits[_index - 1] = _diff;
            anyBitNonZero |= (_diff & 0xFF);
            _index++;
        }
        RETURN (anyBitNonZero ? true : false);
    }
%}.

    index := 1.
    borrow := 0.

    [index <= len1] whileTrue:[
        diff := borrow.
        diff := diff + (digitByteArray basicAt:index).
        index <= len2 ifTrue:[
            diff := diff - (otherDigitByteArray basicAt:index).
        ].

        "/ workaround for
        "/ gcc code generator bug

        (diff >= 0) ifTrue:[
            borrow := 0
        ] ifFalse:[
            borrow := -1.
            diff := diff + 16r100
        ].
        diff ~~ 0 ifTrue:[
            notZero := true
        ].
        digitByteArray basicAt:index put:diff.
        index := index + 1
    ].

    ^ notZero

    "Created: / 5.11.1996 / 16:23:47 / cg"
    "Modified: / 5.11.1996 / 18:56:50 / cg"
    "Modified: / 27.4.1999 / 18:08:23 / stefan"
!

div2
    "private helper for division:
       destructively divide the receiver by 2."

    |prevBit|

%{  /* NOCONTEXT */
    OBJ __digits = __INST(digitByteArray);

    if (__isByteArray(__digits)) {
	int __nBytes = __byteArraySize(__digits);
	unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
	unsigned INT __this, __next;
	int __idx;

	if (__nBytes == 1) {
	    __bp[0] >>= 1;
	    RETURN (self);
	}

	__idx = 1;

#if defined(alpha64)
	if (sizeof(unsigned INT) == 8) {
	    int __endIndex = __nBytes - 8;

	    if (__idx < __endIndex) {
		__this = ((unsigned INT *)__bp)[0];

		while (__idx < __endIndex) {
		    __next = ((unsigned INT *)__bp)[1];
		    __this = (__this >> 1) /* & 0x7FFFFFFFFFFFFFF */;
		    __this |= __next << 63;
		    ((unsigned INT *)__bp)[0] = __this;
		    __this = __next;
		    __bp += 8;
		    __idx += 8;
		}
	    }
	}
#else
# if defined(__LSBFIRST)
	if (sizeof(unsigned int) == 4) {
	    int __endIndex = __nBytes - 4;

	    if (__idx < __endIndex) {
		__this = ((unsigned INT *)__bp)[0];

# if 0
		__idx += 4;
		while (__idx < __endIndex) {
		    __next = ((unsigned int *)__bp)[1];
		    __this = (__this >> 1) /* & 0x7FFFFFF */;
		    __this |= __next << 31;
		    ((unsigned int *)__bp)[0] = __this;
		    __this = __next;

		    __next = ((unsigned int *)__bp)[2];
		    __this = (__this >> 1) /* & 0x7FFFFFF */;
		    __this |= __next << 31;
		    ((unsigned int *)__bp)[1] = __this;
		    __this = __next;

		    __bp += 8;
		    __idx += 8;
		}
		__idx -= 4;
# endif
		while (__idx < __endIndex) {
		    __next = ((unsigned int *)__bp)[1];
		    __this = (__this >> 1) /* & 0x7FFFFFF */;
		    __this |= __next << 31;
		    ((unsigned int *)__bp)[0] = __this;
		    __this = __next;
		    __bp += 4;
		    __idx += 4;
		}
	    }
	}
# endif
#endif

	__this = __bp[0];
	while (__idx < __nBytes) {
	    __next = __bp[1];
	    __this >>= 1;
	    __this |= __next << 7;
	    __bp[0] = __this;
	    __this = __next;
	    __bp++;
	    __idx++;
	}
	__bp[0] = __this >> 1;
	RETURN (self);
    }
%}.

    prevBit := 0.
    digitByteArray size to:1 by:-1 do:[:idx |
	|thisByte|

	thisByte := digitByteArray at:idx.
	digitByteArray at:idx put:((thisByte bitShift:-1) bitOr:prevBit).
	prevBit := (thisByte bitAnd:1) bitShift:7.
    ].

    "
     100000 asLargeInteger div2           
     1000000000000000000000000000 div2  
     10000000000000000000000000000000000000000000 div2
    "                                                     

    "Modified: 5.11.1996 / 16:12:56 / cg"
!

mul2
    "private helper for division:
       destructively multiply the receiver by 2."

    |nBytes "{ Class: SmallInteger }"
     b      "{ Class: SmallInteger }"
     t prevBit|

    nBytes := digitByteArray size.

    b := digitByteArray at:nBytes.
    (b bitAnd:16r80) ~~ 0 ifTrue:[
	"/ need another byte
	nBytes := nBytes + 1.
	t := ByteArray uninitializedNew:nBytes.
	t replaceFrom:1 to:nBytes-1 with:digitByteArray startingAt:1.
	t at:nBytes put:0.
	digitByteArray := t.
    ].

%{
    OBJ __digits = __INST(digitByteArray);

    if (__isByteArray(__digits)) {
	int __nBytes = __intVal(nBytes);
	unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
	unsigned INT __carry = 0, __newCarry,  __this;
	int __idx;

#if defined(alpha64)
	if (sizeof(unsigned INT) == 8) {
	    while (__nBytes >= 8) {
		__this = ((unsigned INT *)__bp)[0];
		__newCarry = (__this >> 63) /* & 1 */;
		((unsigned INT *)__bp)[0] = (__this << 1) | __carry;
		__carry = __newCarry;
		__bp += 8;
		__nBytes -= 8;
	    }
	}
#else
# if defined(__LSBFIRST) || defined(i386) /* XXX actually: LSB_FIRST */
	if (sizeof(unsigned int) == 4) {
	    while (__nBytes >= 4) {
		__this = ((unsigned int *)__bp)[0];
		__newCarry = (__this >> 31) /* & 1 */;
		((unsigned int *)__bp)[0] = (__this << 1) | __carry;
		__carry = __newCarry;
		__bp += 4;
		__nBytes -= 4;
	    }
	}
# endif
#endif
	while (__nBytes) {
	    __this = __bp[0];
	    __newCarry = (__this >> 7) /* & 1 */;
	    __bp[0] = (__this << 1) | __carry;
	    __carry = __newCarry;
	    __bp++;
	    __nBytes--;
	}
	RETURN (self);
    }
%}.

    prevBit := 0.
    1 to:digitByteArray size do:[:idx |
	|thisByte|

	thisByte := digitByteArray at:idx.
	digitByteArray at:idx put:(((thisByte bitShift:1) bitAnd:16rFF) bitOr:prevBit).
	prevBit := (thisByte bitShift:-7) bitAnd:1.
    ].

    "
     100000 asLargeInteger mul2 
     16r7FFFFFFFFFFF copy mul2 hexPrintString
     16rFFFFFFFFFFFF copy mul2 hexPrintString 
     16r7FFFFFFFFFFFFF copy mul2 hexPrintString 
     16rFFFFFFFFFFFFFF copy mul2 hexPrintString 
     10000000000000000000000000000 mul2 
    "

    "Modified: 5.11.1996 / 16:37:32 / cg"
!

mul256
    "private helper for division:
       destructively multiply the receiver by 256."

    |newDigits newSize|

    newSize := digitByteArray size + 1.
    newDigits := ByteArray uninitializedNew:newSize.
"/    newDigits replaceFrom:2 with:digitByteArray startingAt:1.
    newDigits replaceBytesFrom:2 to:newSize with:digitByteArray startingAt:1.
    newDigits at:1 put:0.
    digitByteArray := newDigits

    "Modified: / 20.5.1999 / 09:16:42 / cg"
!

numberOfDigits:nDigits
"/    digitByteArray := ByteArray uninitializedNew:nDigits.
    digitByteArray := ByteArray new:nDigits.
    sign := 1.
!

setDigits:digits
    digitByteArray := digits.
    sign := 1.
!

sign:aNumber
    sign := aNumber
! !

!LargeInteger methodsFor:'testing'!

even
    "return true if the receiver is even"

    ^ (digitByteArray at:1) even
!

negative
    "return true, if the receiver is < 0"

    ^ (sign < 0)
!

odd
    "return true if the receiver is odd"

    ^ (digitByteArray at:1) odd

    "Modified: 18.11.1996 / 22:19:19 / cg"
!

positive
    "return true, if the receiver is >= 0"

    ^ (sign >= 0)
!

sign
    "return the sign of the receiver (-1, 0 or 1)"

    ^ sign
!

strictlyPositive
    "return true, if the receiver is > 0"

    ^ (sign > 0)
! !

!LargeInteger class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/LargeInteger.st,v 1.173 2003-07-07 15:54:32 cg Exp $'
! !