even faster largeInt printString, by doing it in bigger junks (8digits a time)
authorClaus Gittinger <cg@exept.de>
Mon, 01 Dec 1997 19:56:07 +0100
changeset 3121 91de0211651c
parent 3120 56348e25a94f
child 3122 a0be2e69caf0
even faster largeInt printString, by doing it in bigger junks (8digits a time)
Integer.st
--- a/Integer.st	Mon Dec 01 19:54:36 1997 +0100
+++ b/Integer.st	Mon Dec 01 19:56:07 1997 +0100
@@ -41,28 +41,28 @@
     See details in concrete subclasses LargeInteger and SmallInteger.
 
     Mixed mode arithmetic:
-        int op int         -> int
-        int op fix         -> fix; scale is fix's scale
-        int op fraction    -> fraction
-        int op float       -> float
+	int op int         -> int
+	int op fix         -> fix; scale is fix's scale
+	int op fraction    -> fraction
+	int op float       -> float
 
     [Class variables:]
 
-        DefaultDisplayRadix     the radix in which integers present their 
-                                displayString (which is used in inspectors)
-                                If you are to look at many hex numbers, bitmasks
-                                etc. you may set this to 2 or 16.
-                                (avoids typing printStringRadix:.. all the time
-                                 - I know - I am lazy ;-). Default is 10.
+	DefaultDisplayRadix     the radix in which integers present their 
+				displayString (which is used in inspectors)
+				If you are to look at many hex numbers, bitmasks
+				etc. you may set this to 2 or 16.
+				(avoids typing printStringRadix:.. all the time
+				 - I know - I am lazy ;-). Default is 10.
 
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        Number
-        LargeInteger SmallInteger
-        Float ShortFloat Fraction FixedPoint
+	Number
+	LargeInteger SmallInteger
+	Float ShortFloat Fraction FixedPoint
 "
 ! !
 
@@ -126,41 +126,41 @@
      return the value of exceptionBlock."
 
     ErrorSignal handle:[:ex |
-        ^ exceptionBlock value
+	^ exceptionBlock value
     ] do:[
-        |str nextChar value negative|
+	|str nextChar value negative|
 
-        str := aStringOrStream readStream.
+	str := aStringOrStream readStream.
 
-        nextChar := str skipSeparators.
-        (nextChar == $-) ifTrue:[
-            negative := true.
-            nextChar := str nextPeek
-        ] ifFalse:[
-            negative := false
-        ].
-        (nextChar isNil or:[nextChar isDigit not]) ifTrue:[ 
-            "
-             the string does not represent an integer
-            "
-            ^ exceptionBlock value
-        ].
-        value := self readFrom:str radix:10 onError:[^ exceptionBlock value].
-        nextChar := str peek.
-        ((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
-            "-xxr<number> is invalid; should be xxr-<val>"
+	nextChar := str skipSeparators.
+	(nextChar == $-) ifTrue:[
+	    negative := true.
+	    nextChar := str nextPeek
+	] ifFalse:[
+	    negative := false
+	].
+	(nextChar isNil or:[nextChar isDigit not]) ifTrue:[ 
+	    "
+	     the string does not represent an integer
+	    "
+	    ^ exceptionBlock value
+	].
+	value := self readFrom:str radix:10 onError:[^ exceptionBlock value].
+	nextChar := str peek.
+	((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
+	    "-xxr<number> is invalid; should be xxr-<val>"
 
-            negative ifTrue:[
-                'Integer [warning]: invalid (negative) radix ignored' errorPrintCR.
-                negative := false
-            ].
-            str next.
-            value := self readFrom:str radix:value onError:[^ exceptionBlock value]
-        ].
-        negative ifTrue:[
-            ^ value negated
-        ].
-        ^ value
+	    negative ifTrue:[
+		'Integer [warning]: invalid (negative) radix ignored' errorPrintCR.
+		negative := false
+	    ].
+	    str next.
+	    value := self readFrom:str radix:value onError:[^ exceptionBlock value]
+	].
+	negative ifTrue:[
+	    ^ value negated
+	].
+	^ value
     ].
 
     "
@@ -335,11 +335,11 @@
     result := self class basicNew numberOfDigits:n.
 
     1 to:n do:[:index |
-        byte := (anInteger digitAt:index) bitAnd:(self digitAt:index).
-        result digitAt:index put:byte.
+	byte := (anInteger digitAt:index) bitAnd:(self digitAt:index).
+	result digitAt:index put:byte.
     ].
     (byte == 0 or:[n < 5]) ifTrue:[
-        ^ result compressed
+	^ result compressed
     ].
     ^ result
 
@@ -417,8 +417,8 @@
      leftShift if shiftCount > 0; rightShift otherwise.
 
      Notice: the result of bitShift: on negative receivers is not 
-             defined in the language standard (since the implementation
-             is free to choose any internal representation for integers)"
+	     defined in the language standard (since the implementation
+	     is free to choose any internal representation for integers)"
 
     |result 
      prev       "{ Class: SmallInteger }"
@@ -433,146 +433,146 @@
      nDigits    "{ Class: SmallInteger }" |
 
     shiftCount > 0 ifTrue:[
-        "left shift"
+	"left shift"
 
-        digitShift := shiftCount // 8.
-        bitShift := shiftCount \\ 8.
-        n := self digitLength.
+	digitShift := shiftCount // 8.
+	bitShift := shiftCount \\ 8.
+	n := self digitLength.
 
-        "
-         modulu 8 shifts can be done faster ...
-        "
-        bitShift == 0 ifTrue:[
-            result := self class basicNew numberOfDigits:n + digitShift.
-            result sign:self sign.
-            result digits replaceFrom:(digitShift + 1) with:self digits.
-            "
-             no normalize needed, since receiver was already normalized
-            "
-            ^ result
-        ].
+	"
+	 modulu 8 shifts can be done faster ...
+	"
+	bitShift == 0 ifTrue:[
+	    result := self class basicNew numberOfDigits:n + digitShift.
+	    result sign:self sign.
+	    result digits replaceFrom:(digitShift + 1) with:self digits.
+	    "
+	     no normalize needed, since receiver was already normalized
+	    "
+	    ^ result
+	].
 
-        "
-         less-than-8 shifts can be done faster ...
-        "
-        digitShift == 0 ifTrue:[
-            n := n + 1.
-            result := self class basicNew numberOfDigits:n.
-            result sign:self sign.
-            prev := 0.
-            1 to:n-1 do:[:index |
-                byte := self digitAt:index.
-                byte := (byte bitShift:bitShift) bitOr:prev.
-                result digitAt:index put:(byte bitAnd:16rFF).
-                prev := byte bitShift:-8.
-            ].
-            result digitAt:n put:prev.
-            "
-             might have stored a 0-byte ...
-            "
-            prev == 0 ifTrue:[
-                ^ result compressed
-            ].
-            ^ result.
-        ].
+	"
+	 less-than-8 shifts can be done faster ...
+	"
+	digitShift == 0 ifTrue:[
+	    n := n + 1.
+	    result := self class basicNew numberOfDigits:n.
+	    result sign:self sign.
+	    prev := 0.
+	    1 to:n-1 do:[:index |
+		byte := self digitAt:index.
+		byte := (byte bitShift:bitShift) bitOr:prev.
+		result digitAt:index put:(byte bitAnd:16rFF).
+		prev := byte bitShift:-8.
+	    ].
+	    result digitAt:n put:prev.
+	    "
+	     might have stored a 0-byte ...
+	    "
+	    prev == 0 ifTrue:[
+		^ result compressed
+	    ].
+	    ^ result.
+	].
 
-        "
-         slow case ...
-        "
-        n := n + digitShift + 1.
-        result := self class basicNew numberOfDigits:n.
-        result sign:self sign.
-        byte := self digitAt:1.
-        byte := (byte bitShift:bitShift) bitAnd:16rFF.
-        result digitAt:(digitShift + 1) put:byte.
-        revShift := -8 + bitShift.
+	"
+	 slow case ...
+	"
+	n := n + digitShift + 1.
+	result := self class basicNew numberOfDigits:n.
+	result sign:self sign.
+	byte := self digitAt:1.
+	byte := (byte bitShift:bitShift) bitAnd:16rFF.
+	result digitAt:(digitShift + 1) put:byte.
+	revShift := -8 + bitShift.
 	nDigits := self digitLength.
-        2 to:nDigits do:[:index |
-            byte := self digitAt:index.
-            byte2 := self digitAt:index-1.
-            byte := byte bitShift:bitShift.
-            byte2 := byte2 bitShift:revShift.
-            byte := (byte bitOr:byte2) bitAnd:16rFF.
-            result digitAt:(index + digitShift) put:byte.
-        ].
-        byte2 := self digitAt:nDigits.
-        byte2 := (byte2 bitShift:revShift) bitAnd:16rFF.
-        result digitAt:(nDigits + digitShift + 1) put:byte2.
-        "
-         might have stored a 0-byte ...
-        "
-        byte2 == 0 ifTrue:[
-            ^ result compressed
-        ].
-        ^ result
+	2 to:nDigits do:[:index |
+	    byte := self digitAt:index.
+	    byte2 := self digitAt:index-1.
+	    byte := byte bitShift:bitShift.
+	    byte2 := byte2 bitShift:revShift.
+	    byte := (byte bitOr:byte2) bitAnd:16rFF.
+	    result digitAt:(index + digitShift) put:byte.
+	].
+	byte2 := self digitAt:nDigits.
+	byte2 := (byte2 bitShift:revShift) bitAnd:16rFF.
+	result digitAt:(nDigits + digitShift + 1) put:byte2.
+	"
+	 might have stored a 0-byte ...
+	"
+	byte2 == 0 ifTrue:[
+	    ^ result compressed
+	].
+	^ result
     ].
 
     shiftCount < 0 ifTrue:[
-        "right shift"
+	"right shift"
 
-        digitShift := shiftCount negated // 8.
-        bitShift := shiftCount negated \\ 8.
-        n := self digitLength.
+	digitShift := shiftCount negated // 8.
+	bitShift := shiftCount negated \\ 8.
+	n := self digitLength.
 
-        digitShift >= n ifTrue:[
-            ^ 0
-        ].
+	digitShift >= n ifTrue:[
+	    ^ 0
+	].
 
-        "
-         modulu 8 shifts can be done faster ...
-        "
-        bitShift == 0 ifTrue:[
-            n := n-digitShift.
-            result := self class basicNew numberOfDigits:n.
-            result sign:self sign.
-            result digits replaceFrom:1 with:self digits startingAt:(digitShift + 1) .
-            n <= 4 ifTrue:[
-                ^ result compressed
-            ].
-            ^ result
-        ].
+	"
+	 modulu 8 shifts can be done faster ...
+	"
+	bitShift == 0 ifTrue:[
+	    n := n-digitShift.
+	    result := self class basicNew numberOfDigits:n.
+	    result sign:self sign.
+	    result digits replaceFrom:1 with:self digits startingAt:(digitShift + 1) .
+	    n <= 4 ifTrue:[
+		^ result compressed
+	    ].
+	    ^ result
+	].
 
-        "
-         less-than-8 shifts can be done faster ...
-        "
-        digitShift == 0 ifTrue:[
-            result := self class basicNew numberOfDigits:n.
-            result sign:self sign.
-            prev := 0.
-            bitShift := bitShift negated.
-            revShift := 8 + bitShift.
-            n to:1 by:-1 do:[:index |
-                byte := self digitAt:index.
-                next := (byte bitShift:revShift) bitAnd:16rFF.
-                byte := (byte bitShift:bitShift) bitOr:prev.
-                result digitAt:index put:(byte bitAnd:16rFF).
-                prev := next.
-            ].
-            (n <= 5) ifTrue:[
-                ^ result compressed
-            ].
-            ^ result
-        ].
+	"
+	 less-than-8 shifts can be done faster ...
+	"
+	digitShift == 0 ifTrue:[
+	    result := self class basicNew numberOfDigits:n.
+	    result sign:self sign.
+	    prev := 0.
+	    bitShift := bitShift negated.
+	    revShift := 8 + bitShift.
+	    n to:1 by:-1 do:[:index |
+		byte := self digitAt:index.
+		next := (byte bitShift:revShift) bitAnd:16rFF.
+		byte := (byte bitShift:bitShift) bitOr:prev.
+		result digitAt:index put:(byte bitAnd:16rFF).
+		prev := next.
+	    ].
+	    (n <= 5) ifTrue:[
+		^ result compressed
+	    ].
+	    ^ result
+	].
 
-        "
-         slow case ...
-        "
-        nn := n-digitShift.
-        result := self class basicNew numberOfDigits:nn.
-        result sign:self sign.
+	"
+	 slow case ...
+	"
+	nn := n-digitShift.
+	result := self class basicNew numberOfDigits:nn.
+	result sign:self sign.
 
-        prev := 0.
-        bitShift := bitShift negated.
-        revShift := 8 + bitShift.
-        n to:(1 + digitShift) by:-1 do:[:index |
-            byte := self digitAt:index.
-            next := (byte bitShift:revShift) bitAnd:16rFF.
-            byte := (byte bitShift:bitShift) bitOr:prev.
-            result digitAt:(index - digitShift) put:byte.
-            prev := next.
-        ].
-        "the last stored byte ..."
-        ^ result compressed
+	prev := 0.
+	bitShift := bitShift negated.
+	revShift := 8 + bitShift.
+	n to:(1 + digitShift) by:-1 do:[:index |
+	    byte := self digitAt:index.
+	    next := (byte bitShift:revShift) bitAnd:16rFF.
+	    byte := (byte bitShift:bitShift) bitOr:prev.
+	    result digitAt:(index - digitShift) put:byte.
+	    prev := next.
+	].
+	"the last stored byte ..."
+	^ result compressed
     ].
 
     ^ self "no shift"
@@ -593,8 +593,8 @@
     result := self class basicNew numberOfDigits:n.
 
     1 to:n do:[:index |
-        byte := (anInteger digitAt:index) bitAnd:(self digitAt:index).
-        byte ~~ 0 ifTrue:[^ true].
+	byte := (anInteger digitAt:index) bitAnd:(self digitAt:index).
+	byte ~~ 0 ifTrue:[^ true].
     ].
     ^ false
 
@@ -625,11 +625,11 @@
     result := self class basicNew numberOfDigits:n.
 
     1 to:n do:[:index |
-        byte := (anInteger digitAt:index) bitXor:(self digitAt:index).
-        result digitAt:index put:byte.
+	byte := (anInteger digitAt:index) bitXor:(self digitAt:index).
+	result digitAt:index put:byte.
     ].
     byte == 0 ifTrue:[
-        ^ result compressed
+	^ result compressed
     ].
     ^ result
 
@@ -677,11 +677,11 @@
     maxBytes := self digitLength.
     bitIndex := 0.
     1 to:maxBytes do:[:byteIndex |
-        byte := self digitAt:byteIndex.
-        byte ~~ 0 ifTrue:[
-            ^ bitIndex + byte lowBit
-        ].
-        bitIndex := bitIndex + 8
+	byte := self digitAt:byteIndex.
+	byte ~~ 0 ifTrue:[
+	    ^ bitIndex + byte lowBit
+	].
+	bitIndex := bitIndex + 8
     ].
     ^ -1
 
@@ -794,7 +794,7 @@
 
     d := aFraction denominator.
     ^ (Fraction numerator:(aFraction numerator - (self * d))
-              denominator:d)
+	      denominator:d)
 
     "Modified: 28.7.1997 / 19:08:30 / cg"
 !
@@ -803,7 +803,7 @@
     "sent when a fraction does not know how to multiply the receiver, an integer"
 
     ^ (Fraction numerator:(self * aFraction numerator)
-              denominator:aFraction denominator)
+	      denominator:aFraction denominator)
 
     "Modified: 28.7.1997 / 19:08:27 / cg"
 !
@@ -812,8 +812,8 @@
     "sent when a fraction does not know how to divide the receiver, an integer"
 
     ^ Fraction 
-        numerator:aFraction numerator
-        denominator:(self * aFraction denominator)
+	numerator:aFraction numerator
+	denominator:(self * aFraction denominator)
 
     "Modified: 28.7.1997 / 19:08:23 / cg"
 !
@@ -825,7 +825,7 @@
 
     d := aFraction denominator.
     ^ Fraction numerator:(aFraction numerator + (self * d))
-              denominator:d
+	      denominator:d
 
     "Modified: 28.7.1997 / 19:08:11 / cg"
 ! !
@@ -847,12 +847,12 @@
     shift := selfLowBit min:argLowBit.
     argAbs := argAbs bitShift:(argLowBit negated).
     [selfAbs = 0] whileFalse:[
-        selfAbs := selfAbs bitShift:(selfLowBit negated).
-        selfAbs < argAbs ifTrue:[
-            t := selfAbs. selfAbs := argAbs. argAbs := t
-        ].
-        selfAbs := selfAbs - argAbs.
-        selfLowBit := selfAbs lowBit - 1.
+	selfAbs := selfAbs bitShift:(selfLowBit negated).
+	selfAbs < argAbs ifTrue:[
+	    t := selfAbs. selfAbs := argAbs. argAbs := t
+	].
+	selfAbs := selfAbs - argAbs.
+	selfLowBit := selfAbs lowBit - 1.
     ].
     ^ argAbs bitShift:shift
 
@@ -885,8 +885,8 @@
      more performance (where the remainder is generated as a side effect of division)"
 
     ^ Array
-        with:(self // aNumber)
-        with:(self \\ aNumber)
+	with:(self // aNumber)
+	with:(self \\ aNumber)
 
     "  
      10 divMod:3  
@@ -904,19 +904,19 @@
     |p i|
 
     (self < 2) ifTrue:[
-        self < 0 ifTrue:[
-            "/
-            "/ requested factorial of a negative number
-            "/
-            ^ DomainErrorSignal raiseErrorString:'factorial of negative number'
-        ].
-        ^ 1
+	self < 0 ifTrue:[
+	    "/
+	    "/ requested factorial of a negative number
+	    "/
+	    ^ DomainErrorSignal raiseErrorString:'factorial of negative number'
+	].
+	^ 1
     ].
     p := 2.
     i := 3.
     [i <= self] whileTrue:[
-        p := p * i.
-        i := i + 1.
+	p := p * i.
+	i := i + 1.
     ].
     ^ p
 
@@ -938,7 +938,7 @@
     "return fac(self) (i.e. 1*2*3...*self) using a recursive algorithm."
 
     (self >= 2) ifTrue:[
-        ^ self * (self - 1) factorialR
+	^ self * (self - 1) factorialR
     ].
     ^ 1
 
@@ -975,7 +975,7 @@
      (use fastFib instead and dont ever try 60 fib ...)"
 
     (self > 1) ifTrue:[
-        ^ (self - 1) fib + (self - 2) fib
+	^ (self - 1) fib + (self - 2) fib
     ].
     ^ 1
 
@@ -987,7 +987,7 @@
 
     "
      ds3100  486/50  Indy(no cache) P5/166       P5/166
-                                    interpreted  compiled  
+				    interpreted  compiled  
      20804    4800     2145         14996        1303
     "
 
@@ -1024,9 +1024,9 @@
     argAbs := anInteger abs.
 
     selfAbs < argAbs ifTrue:[
-        t := selfAbs.
-        selfAbs := argAbs.
-        argAbs := t.
+	t := selfAbs.
+	selfAbs := argAbs.
+	argAbs := t.
     ].
 
     argAbs = 0 ifTrue: [^ selfAbs].
@@ -1133,16 +1133,16 @@
     "return a string representation of the receiver in the specified
      radix (without the initial XXr)"
 
-    |num s divMod mod r5 num5|
+    |num s divMod mod r nD numN|
 
     (aRadix between:2 and:36) ifFalse:[
-        self error:'invalid radix'.
-        ^ self printStringRadix:10
+	self error:'invalid radix'.
+	^ self printStringRadix:10
     ].
 
     (self = 0) ifTrue:[^ '0'].
     (self < 0) ifTrue:[
-        ^ '-' , (self negated printStringRadix:aRadix)
+	^ '-' , (self negated printStringRadix:aRadix)
     ].
 
     "
@@ -1159,38 +1159,50 @@
     num := self.
     num = 0 ifTrue:[^ '0'].
 
-    s := ''.
+    s := WriteStream on:''.
 
-    r5 := aRadix*aRadix.
-    r5 := r5*r5.
-    r5 := r5*aRadix.
+    "/ instead of computing the quotient and remainder
+    "/ against radix, do it in junks of 5 or 8 digits.
+    "/ This reduces the number of LargeInt-divisions
+    "/ by that factor (turning them into smallInt divisions
+    "/ within that junk) and speeds up the conversions noticably.
 
-    [num >= r5] whileTrue:[
-	"/
-	"/ chop off 5 digits.
+    r := aRadix*aRadix.   "/ radix^2
+    r := r*r.             "/ radix^4
+    aRadix <= 10 ifTrue:[
+	r := r*r.         "/ radix^8
+	nD := 8.
+    ] ifFalse:[
+	r := r*aRadix.    "/ radix^5
+	nD := 5.
+    ].
+
+    [num >= r] whileTrue:[
 	"/
-	divMod := num divMod:r5.
+	"/ chop off nD digits.
+	"/
+	divMod := num divMod:r.
 	num := divMod at:1.
-	num5 := divMod at:2.
+	numN := divMod at:2.
 
 	"/ process them
-	5 timesRepeat:[
-            divMod := num5 divMod:aRadix.
-            num5 := divMod at:1.
-            mod := divMod at:2.
-            s := (Character digitValue:mod) asString , s.
+	nD timesRepeat:[
+	    divMod := numN divMod:aRadix.
+	    numN := divMod at:1.
+	    mod := divMod at:2.
+	    s nextPut: (Character digitValue:mod).
 	].
     ].
 
     [num ~= 0] whileTrue:[
-        divMod := num divMod:aRadix.
-        num := divMod at:1.
-        mod := divMod at:2.
-        s := (Character digitValue:mod) asString , s.
+	divMod := num divMod:aRadix.
+	num := divMod at:1.
+	mod := divMod at:2.
+	s nextPut: (Character digitValue:mod).
     ].
-    ^ s
+    ^ s contents reverse
 
-    "Modified: 29.10.1996 / 21:27:21 / cg"
+    "Modified: / 17.11.1997 / 16:27:45 / cg"
 !
 
 printStringRadix:aRadix size:sz fill:fillCharacter
@@ -1302,20 +1314,20 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else if (__isLargeInteger(self)) {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     } else {
-        goto bad;
+	goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else if (__isLargeInteger(anInteger)) {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     } else {
-        goto bad;
+	goto bad;
     }
     rslt = val1 & val2;
     RETURN(__MKINT(rslt));
@@ -1335,20 +1347,20 @@
     int val1, val2, rslt;
 
     if (__isSmallInteger(self)) {
-        val1 = __intVal(self);
+	val1 = __intVal(self);
     } else if (__isLargeInteger(self)) {
-        val1 = __longIntVal(self);
-        if (!val1) goto bad;
+	val1 = __longIntVal(self);
+	if (!val1) goto bad;
     } else {
-        goto bad;
+	goto bad;
     }
     if (__isSmallInteger(anInteger)) {
-        val2 = __intVal(anInteger);
+	val2 = __intVal(anInteger);
     } else if (__isLargeInteger(anInteger)) {
-        val2 = __longIntVal(anInteger);
-        if (!val2) goto bad;
+	val2 = __longIntVal(anInteger);
+	if (!val2) goto bad;
     } else {
-        goto bad;
+	goto bad;
     }
     rslt = val1 | val2;
     RETURN(__MKINT(rslt));
@@ -1455,5 +1467,5 @@
 !Integer class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.71 1997-10-28 19:12:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.72 1997-12-01 18:56:07 cg Exp $'
 ! !