LargeInteger.st
changeset 3984 45a76e2f4236
parent 3910 73d735ca6311
child 4137 f85d341a13e4
--- a/LargeInteger.st	Sun Feb 14 11:37:42 1999 +0100
+++ b/LargeInteger.st	Sun Feb 14 12:15:07 1999 +0100
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:3.4.1 on 13-feb-1998 at 15:51:41'                    !
+
 Integer subclass:#LargeInteger
 	instanceVariableNames:'sign digitByteArray'
 	classVariableNames:''
@@ -412,65 +414,58 @@
      The result is truncated toward negative infinity and negative,
      if the operands signs differ."
 
-    |otherSign divMod quo abs "{ Class: SmallInteger }" n|
-
-    otherSign := aNumber sign.
+    |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 ...
     "
-    (aNumber class == SmallInteger) ifTrue:[
-	abs := aNumber.
-	abs := abs abs.
-	(abs between:1 and:16r003fffff) ifTrue:[
-	    divMod := self absFastDiv:abs.
-	    quo := divMod at:1.
-	    (sign == otherSign) ifTrue:[^ quo].
-
-	    "/ stupid adjust ...
-	    (divMod at:2) == 0 ifFalse:[
-		^ (quo sign:-1) - 1
-	    ].
-	    ^ quo sign:-1
-	].
-	n := aNumber asLargeInteger.
+    (cls == SmallInteger) ifTrue:[
+        abs := aNumber.
+        abs := abs abs.
+        (abs between:1 and:16r00ffffff) ifTrue:[
+            divMod := self absFastDiv:abs.
+        ] ifFalse:[
+            n := abs asLargeInteger.
+        ].
     ] ifFalse:[
-	n := aNumber
+        "
+         if the argument is not a largeInteger, coerce
+        "
+        (cls == self class) ifFalse:[
+            ^ self retry:#// coercing:aNumber
+        ].
+        n := aNumber
     ].
 
+    divMod isNil ifTrue:[
+        divMod := self absDiv: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
+
     "
-     if the argument is not a largeInteger, coerce
-    "
-    (n class == self class) ifFalse:[
-	^ self retry:#// coercing:aNumber
-    ].
-
-    divMod := self absDiv:n.
-
-    (sign == otherSign) ifTrue:[^ divMod at:1].
-
-    "/ stupid adjust for truncation ...
-    quo := divMod at:1.
-    (divMod at:2) == 0 ifFalse:[
-	^ (quo sign:-1) - 1
-    ].
-    ^ quo sign:-1
-
-    "
-     900 // 400  
-     -900 // 400 
-     900 // -400  
-     -900 // -400
-
-     9000000000 // 4000000000
-     -9000000000 // 4000000000 
-     9000000000 // -4000000000 
-     -9000000000 // -4000000000
+     (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                   
+     900 quo: -400                   
      -900 quo: -400 
 
      9000000000 quo: 4000000000   
@@ -479,53 +474,70 @@
      -9000000000 quo: -4000000000 
     "
 
-    "Modified: 5.11.1996 / 16:39:36 / cg"
+    "Modified: / 5.11.1996 / 16:39:36 / cg"
+    "Modified: / 13.2.1998 / 15:10:09 / stefan"
 !
 
 \\ aNumber
-    "return the remainder of division of the receiver by the argument, aNumber.
-     The sign of the result is that of aNumber."
-
-    |abs rem|
-
-    abs := aNumber abs.
+    "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
+     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:16r003fffff) ifTrue:[
-	    rem := (self absFastDiv:abs) at:2.
-	] ifFalse:[
-	    rem := (self absDiv:abs asLargeInteger) at:2
-	].
+        (abs between:1 and:16r00ffffff) ifTrue:[
+            rem := (self absFastDiv:abs) at:2.
+        ] ifFalse:[
+            rem := (self absDiv:abs asLargeInteger) at:2
+        ].
     ] ifFalse:[
-	"
-	 if the argument is not a largeInteger, coerce
-	"
-	(aNumber class == self class) ifFalse:[
-	    ^ self retry:#\\ coercing:aNumber
-	].
-
-	rem := (self absDiv:abs) at:2.
+        "
+         if the argument is not a largeInteger, coerce
+        "
+        (aNumber class == self class) ifFalse:[
+            ^ self retry:#\\ coercing:aNumber
+        ].
+
+        rem := (self absDiv:abs) at:2.
     ].
 
-    aNumber negative ifTrue:[
-	^ rem sign:-1
+    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
 
     "
-     900 \\ 400    
-     -900 \\ 400  
-     900 \\ -400   
-     -900 \\ -400  
-
-     9000000000 \\ 4000000000   
-     -9000000000 \\ 4000000000  
-     9000000000 \\ -4000000000  
-     -9000000000 \\ -4000000000 
+     (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     
@@ -543,7 +555,8 @@
      -9000000000 rem: -4000000000  
     "
 
-    "Modified: 5.11.1996 / 17:10:10 / cg"
+    "Modified: / 5.11.1996 / 17:10:10 / cg"
+    "Modified: / 13.2.1998 / 14:25:01 / stefan"
 !
 
 divMod:aNumber
@@ -552,33 +565,35 @@
      The result is only defined for positive receiver and
      argument."
 
-    "
-     this is the common case, dividing by a SmallInteger.
-     Use a special method for this case ...
-    "
-    (aNumber class == SmallInteger) ifTrue:[
-	^ self absFastDiv:aNumber abs.
+    |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 absFastDiv:aNumber abs.
+        ].
+        n := aNumber asLargeInteger.
+    ] ifFalse:[
+        (cls == self class) ifFalse:[
+            ^ super divMod:aNumber            
+        ].
+        n := aNumber.
     ].
 
-    "
-     if the argument is not a largeInteger, coerce
-    "
-    (aNumber class == self class) ifTrue:[
-	^ self absDiv:aNumber abs
-    ].
-
-    ^ super divMod:aNumber
+    ^ self absDiv:n abs
 
     "
      9000000000 // 4000000000   => 2
-
      9000000000 \\ 4000000000   => 1000000000 
-
      9000000000 divMod: 4000000000   => #(2 1000000000)
     "
 
-    "Modified: 29.10.1996 / 20:44:23 / cg"
-    "Created: 29.10.1996 / 21:22:05 / cg"
+    "Created: / 29.10.1996 / 21:22:05 / cg"
+    "Modified: / 13.2.1998 / 15:32:54 / stefan"
 !
 
 negated
@@ -663,26 +678,26 @@
      Use a special method for this case ...
     "
     (aNumber class == SmallInteger) ifTrue:[
-	abs := aNumber.
-	abs := abs abs.
-	(abs between:1 and:16r003fffff) ifTrue:[
-	    quo := (self absFastDiv:abs) at:1.
-	    (sign == otherSign) ifTrue:[^ quo].
-	    ^ quo sign:-1
-	]
+        abs := aNumber.
+        abs := abs abs.
+        (abs between:1 and:16r00ffffff) ifTrue:[
+            quo := (self absFastDiv: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
+        ^ self retry:#quo: coercing:aNumber
     ].
 
     sign < 0 ifTrue:[
-	(sign == otherSign) ifTrue:[^ (self absDiv:aNumber negated) at:1].
+        (sign == otherSign) ifTrue:[^ (self absDiv:aNumber negated) at:1].
     ] ifFalse:[
-	(sign == otherSign) ifTrue:[^ (self absDiv:aNumber) at:1].
+        (sign == otherSign) ifTrue:[^ (self absDiv:aNumber) at:1].
     ].
     ^ ((self absDiv:aNumber) at:1) sign:-1
 
@@ -708,7 +723,8 @@
      -9000000000 quo: -4000000000  
     "
 
-    "Modified: 5.11.1996 / 14:14:17 / cg"
+    "Modified: / 5.11.1996 / 14:14:17 / cg"
+    "Modified: / 13.2.1998 / 13:56:05 / stefan"
 !
 
 rem:aNumber
@@ -722,26 +738,26 @@
      Use special code for this case ...
     "
     (aNumber class == SmallInteger) ifTrue:[
-	abs := aNumber.
-	abs := abs abs.
-	(abs between:1 and:16r003fffff) ifTrue:[
-	    rem := (self absFastDiv:abs) at:2.
-	] ifFalse:[
-	    rem := (self absDiv:(abs asLargeInteger)) at:2
-	].
+        abs := aNumber.
+        abs := abs abs.
+        (abs between:1 and:16r00ffffff) ifTrue:[
+            rem := (self absFastDiv:abs) at:2.
+        ] ifFalse:[
+            rem := (self absDiv:(abs asLargeInteger)) at:2
+        ].
     ] ifFalse:[
-	"
-	 if the argument is not a largeInteger, coerce
-	"
-	(aNumber class == self class) ifFalse:[
-	    ^ self retry:#\\ coercing:aNumber
-	].
-
-	rem := (self absDiv:aNumber) at:2
+        "
+         if the argument is not a largeInteger, coerce
+        "
+        (aNumber class == self class) ifFalse:[
+            ^ self retry:#\\ coercing:aNumber
+        ].
+
+        rem := (self absDiv:aNumber) at:2
     ].
 
     sign < 0 ifTrue:[
-	^ rem sign:-1
+        ^ rem sign:-1
     ].
     ^ rem
 
@@ -767,7 +783,8 @@
      -9000000000 rem: -4000000000   
     "
 
-    "Modified: 5.11.1996 / 14:02:59 / cg"
+    "Modified: / 5.11.1996 / 14:02:59 / cg"
+    "Modified: / 13.2.1998 / 13:56:11 / stefan"
 ! !
 
 !LargeInteger methodsFor:'bit operators'!
@@ -1251,6 +1268,12 @@
     "return true, if the argument, aNumber has the same value as
      the receiver"
 
+    "/ speed up compare to 0
+
+    (aNumber == 0 and:[sign == 0]) ifTrue:[
+        ^ true
+    ].
+
     (aNumber class == self class) ifFalse:[
 	"/
 	"/ here, we depend on the fact, that largeinteger
@@ -1263,6 +1286,8 @@
     ].
     (aNumber sign == sign) ifFalse:[^ false].
     ^ self absEq:aNumber
+
+    "Modified: / 13.2.1998 / 11:43:15 / stefan"
 !
 
 > aNumber
@@ -1638,62 +1663,65 @@
      Used as a helper for \\, //, rem: and quo:.
      This method needs a rewrite."
 
-    |tmp1 tmp2 
+    |dividend divisor 
      quo
      count "{ Class: SmallInteger }" |
 
     anInteger == 0 ifTrue:[
-	^ DivisionByZeroSignal raise
+        ^ DivisionByZeroSignal raise
     ].
 
     self = anInteger ifTrue:[
-	^ Array with:1 with:0
+        ^ Array with:1 with:0
     ].
 
-    tmp1 := self simpleDeepCopy.
-    tmp1 sign:1.
-    tmp2 := anInteger simpleDeepCopy.
-    tmp2 sign:1.
-
-    (tmp1 < tmp2) ifTrue:[
-	^ Array with:0 with:tmp1 
+    dividend := self simpleDeepCopy sign:1.
+    divisor := anInteger simpleDeepCopy sign:1.
+    (dividend < divisor) ifTrue:[
+        ^ Array with:0 with:dividend 
     ].
 
     count := 0.
-    [tmp2 absLess: tmp1] whileTrue:[
-	tmp2 mul2.
-	count := count + 1
+    [divisor absLessEq:dividend] whileTrue:[
+        divisor mul2.
+        count := count + 1
     ].
 
-    tmp2 div2.
+    divisor div2.
 
     quo := 0 asLargeInteger. 
     quo sign:1.
 
     [count == 0] whileFalse:[
-	quo mul2.
-	(tmp1 absLess:tmp2) ifFalse:[
-	    quo digits at:1 put:((quo digits at:1) bitOr:1).
-	    (tmp1 absSubtract: tmp2) ifFalse:[
-		"/ difference is zero; continue shifting
-		count := count - 1.
-		[count >= 8] whileTrue:[
-		    quo mul256.
-		    count := count - 8
-		].
-		[count == 0] whileFalse:[
-		    quo mul2.
-		    count := count - 1.
-		].
-		^ Array with:quo compressed with:tmp1 compressed
-	    ].
-	].
-	tmp2 div2.
-	count := count - 1
+        quo mul2.
+        (dividend absLess:divisor) ifFalse:[
+            quo digits at:1 put:((quo digits at:1) bitOr:1).
+            (dividend absSubtract: divisor) ifFalse:[
+                "/ difference is zero; continue shifting
+                count := count - 1.
+                [count >= 8] whileTrue:[
+                    quo mul256.
+                    count := count - 8
+                ].
+                [count == 0] whileFalse:[
+                    quo mul2.
+                    count := count - 1.
+                ].
+                ^ Array with:quo compressed with:dividend compressed
+            ].
+        ].
+        divisor div2.
+        count := count - 1
     ].
-    ^ Array with:quo compressed with:tmp1 compressed
-
-    "Modified: 5.11.1996 / 18:40:24 / cg"
+    ^ Array with:quo compressed with:dividend compressed
+
+    "
+     16000000000 absDiv:4000000000   
+     16000000000 absDiv:3000000000
+    "
+
+    "Modified: / 5.11.1996 / 18:40:24 / cg"
+    "Modified: / 13.2.1998 / 12:22:41 / stefan"
 !
 
 absEq:aLargeInteger
@@ -1736,12 +1764,12 @@
      ok|
 
     aPositiveSmallInteger == 0 ifTrue:[
-	^ DivisionByZeroSignal raise
+        ^ DivisionByZeroSignal raise
     ].
 
 "This cannot happen (if always normalized)
     self < aPositiveSmallInteger ifTrue:[
-	^ Array with:0 with:self
+        ^ Array with:0 with:self
     ].
 "
     count := digitByteArray size.
@@ -1756,67 +1784,67 @@
     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;
+        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;
 
 #ifdef i386
-	if (divisor < 0xFFFF) {
-	    if ((index & 1) == 0) { /* even number of bytes */
-		while (index > 1) {
-		    unsigned INT t;
-		    unsigned INT div;
+        if (divisor <= 0xFFFF) {
+            if ((index & 1) == 0) { /* even number of bytes */
+                while (index > 1) {
+                    unsigned INT t;
+                    unsigned INT div;
 
 # ifdef i386 /* LSB_FIRST */
-		    index -= 2;
-		    t = *((unsigned short *)(&digitBytes[index]));
+                    index -= 2;
+                    t = *((unsigned short *)(&digitBytes[index]));
 # else
-		    index--;
-		    t = digitBytes[index];
-		    index--;
-		    t = (t << 8) | digitBytes[index];
+                    index--;
+                    t = digitBytes[index];
+                    index--;
+                    t = (t << 8) | digitBytes[index];
 # endif
-		    t = t | (rest << 16);
-		    div = t / divisor;
-		    rest = t % divisor;
+                    t = t | (rest << 16);
+                    div = t / divisor;
+                    rest = t % divisor;
 # ifdef i386 /* LSB_FIRST */
-		    *((unsigned short *)(&resultBytes[index])) = (div & 0xFFFF);
+                    *((unsigned short *)(&resultBytes[index])) = (div & 0xFFFF);
 # else
-		    resultBytes[index+1] = (div >> 8);
-		    resultBytes[index] = (div & 0xFF);
+                    resultBytes[index+1] = (div >> 8);
+                    resultBytes[index] = (div & 0xFF);
 # endif
-		}
-	    }
-	}
+                }
+            }
+        }
 #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);
-	ok = true;
-
-	/*
-	 * no need to normalize ?
-	 */
-	while ((index0 > sizeof(INT)) && (resultBytes[index0]==0)) {
-	    index0--;
-	}
-
-	if ((index0 > sizeof(INT))
-	 && (resultBytes[index0-1])) {
-	    RETURN ( __ARRAY_WITH2(result, prevRest));
-	}
+        while (index > 0) {
+            unsigned INT t;
+
+            index--;
+            t = digitBytes[index];
+            t = t | (rest << 8);
+            resultBytes[index] = t / divisor;
+            rest = t % divisor;
+        }
+        prevRest = __MKSMALLINT(rest);
+        ok = true;
+
+        /*
+         * no need to normalize ?
+         */
+        while ((index0 > sizeof(INT)) && (resultBytes[index0]==0)) {
+            index0--;
+        }
+
+        if ((index0 > sizeof(INT))
+         && (resultBytes[index0-1])) {
+            RETURN ( __ARRAY_WITH2(result, prevRest));
+        }
     }
 %}.
     "
@@ -1824,10 +1852,15 @@
      (could also do a primitiveFailure here)
     "
     ok ifFalse:[
-	self primitiveFailed
+        self primitiveFailed
     ].
 
     ^ Array with:(result compressed) with:prevRest
+
+    "
+     ((16r1234 asLargeInteger absFastDiv:16rffff) at:2) printStringRadix:16
+     ((16r00123456 asLargeInteger absFastDiv:16rffffff) at:2) printStringRadix:16
+    "
 !
 
 absFastMinus:aSmallInteger
@@ -2027,6 +2060,44 @@
     "Modified: 5.11.1996 / 18:37:27 / 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 digits.
+    otherLen := otherDigitByteArray size.
+
+    [(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].
+            (d1 > d2) ifTrue:[^ false].
+        ].
+        myLen := myLen - 1
+    ].
+    ^ true
+
+    "Modified: / 5.11.1996 / 18:37:27 / cg"
+    "Created: / 13.2.1998 / 12:19:45 / stefan"
+!
+
 absMinus:aLargeInteger
     "return a LargeInteger representing abs(self) - abs(theArgument)"
 
@@ -2668,5 +2739,5 @@
 !LargeInteger class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/LargeInteger.st,v 1.72 1998-10-31 11:37:04 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/LargeInteger.st,v 1.73 1999-02-14 11:15:05 stefan Exp $'
 ! !