Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 11 Feb 2016 16:21:50 +0000
branchjv
changeset 19167 699eef1bc815
parent 19158 cdce727939ab (current diff)
parent 19166 22f1ee605c16 (diff)
child 19225 9e8abf62f932
Merge
Class.st
HashStream.st
Integer.st
LargeInteger.st
SHA1Stream.st
--- a/Class.st	Mon Feb 08 06:59:19 2016 +0100
+++ b/Class.st	Thu Feb 11 16:21:50 2016 +0000
@@ -1081,7 +1081,7 @@
 
     "/ (self nameSpace at:self nameWithoutNamespacePrefix ifAbsent:nil)
     "/ or
-    (Smalltalk at:name) ~~ self ifTrue:[
+    (name isSymbol and:[(Smalltalk at:name) == self]) ifFalse:[
         ^ nil
     ].
     ^ self nameSpace
@@ -2091,6 +2091,7 @@
 ! !
 
 
+
 !Class methodsFor:'adding & removing'!
 
 removeFromSystem
--- a/HashStream.st	Mon Feb 08 06:59:19 2016 +0100
+++ b/HashStream.st	Thu Feb 11 16:21:50 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Stream subclass:#HashStream
 	instanceVariableNames:''
 	classVariableNames:''
@@ -270,6 +272,14 @@
     "Created: / 17.3.1999 / 15:10:03 / stefan"
 ! !
 
+!HashStream methodsFor:'compatibility - squeak'!
+
+digestMessage:bytes
+    "SQUEAK: answer the digest of bytes"
+
+    ^ self hashValueOf:bytes
+! !
+
 !HashStream methodsFor:'not implemented'!
 
 next
@@ -283,22 +293,22 @@
 
 !HashStream methodsFor:'operations'!
 
-digestMessage:bytes
+hashValueOf:bytes
     "answer the digest of bytes"
 
-    self reset.
-    self nextPutAll:bytes.
-
-    ^ self hashValue.
+    ^ self 
+        reset;
+        nextPutAll:bytes;
+        hashValue.
 
     "
         SHA1Stream new 
-                digestMessage:'123456789abcdefg';
-                digestMessage:'123456789abcdefg'
+                hashValueOf:'123456789abcdefg';
+                hashValueOf:'123456789abcdefg'
 
         (SHA1Stream new hmac key:'123456') 
-                digestMessage:'123456789abcdefg';
-                digestMessage:'123456789abcdefg'
+                hashValueOf:'123456789abcdefg';
+                hashValueOf:'123456789abcdefg'
 
         (SHA1Stream new hmac key:'123456') 
                 nextPutAll:'123456789abcdefg';
@@ -347,17 +357,6 @@
     "Modified (comment): / 23-01-2012 / 10:01:20 / cg"
 !
 
-hashValueOf:aString
-    "for convenience:
-     return the value of the computed hash of aString"
-
-    self reset.
-    self nextPutAll:aString.
-    ^ self hashValue
-
-    "Created: / 18-01-2012 / 17:26:25 / cg"
-!
-
 isReadable
     "return true, if reading is supported by the recevier.
      Always return false here"
@@ -415,7 +414,7 @@
 !
 
 nextPutAll:aCollection
-    "Hash streams handle Strings and ByteArrays in nextPut:"
+    "Hash streams handle Strings and ByteArrays in #nextPutBytes:"
 
     aCollection isByteCollection ifTrue:[
         self nextPutBytes:(aCollection byteSize) from:aCollection startingAt:1.
@@ -427,6 +426,13 @@
     "Modified: / 09-01-2012 / 13:02:44 / cg"
 !
 
+nextPutByte:aByte
+    "add the hash of anObject to the computed hash so far.
+     aByte can be a SmallInteger <= 255"
+
+    self nextPutBytes:1 from:(ByteArray with:aByte) startingAt:1.
+!
+
 nextPutBytes:count from:anObject startingAt:start
     "write count bytes from an object starting at index start.
      Return the number of bytes written.
@@ -441,10 +447,10 @@
 !HashStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/HashStream.st,v 1.30 2014-10-02 17:48:04 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/HashStream.st,v 1.30 2014-10-02 17:48:04 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/Integer.st	Mon Feb 08 06:59:19 2016 +0100
+++ b/Integer.st	Thu Feb 11 16:21:50 2016 +0000
@@ -15,17 +15,17 @@
 "{ NameSpace: Smalltalk }"
 
 Number subclass:#Integer
-        instanceVariableNames:''
-        classVariableNames:'BCDConversionErrorSignal PrimeCache'
-        poolDictionaries:''
-        category:'Magnitude-Numbers'
+	instanceVariableNames:''
+	classVariableNames:'BCDConversionErrorSignal PrimeCache'
+	poolDictionaries:''
+	category:'Magnitude-Numbers'
 !
 
 Object subclass:#ModuloNumber
-        instanceVariableNames:'modulus reciprocal shift'
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Integer
+	instanceVariableNames:'modulus reciprocal shift'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Integer
 !
 
 !Integer class methodsFor:'documentation'!
@@ -3032,12 +3032,11 @@
 
 factorial
     "return fac(self) (i.e. 1*2*3...*self) using an iterative algorithm.
-     This is slightly faster than the recursive algorithm, and does not
-     suffer from stack overflow problems (with big receivers)"
-
-    |p i|
-
-    (self < 2) ifTrue:[
+     This chooses a good algorithm, based on the receiver.
+     Some heuristics here, which has to do with the speed of largeInteger
+     arrithmetic."
+
+    (self <= 20) ifTrue:[
         self < 0 ifTrue:[
             "/
             "/ requested factorial of a negative number
@@ -3049,8 +3048,239 @@
                 arguments:#()
                 errorString:'factorial of negative number'
         ].
-        ^ 1
+        ^ #(1 1 2 6 24 120 720 5040 40320 362880 3628800 39916800
+          479001600 6227020800 87178291200 1307674368000 20922789888000 
+          355687428096000 6402373705728000 121645100408832000
+          2432902008176640000) at:self+1
+    ].
+    
+"/    self < 80000 ifTrue:[
+"/        ^ self factorialHalf
+"/    ].    
+    ^ self factorialEvenOdd
+
+    "
+     10 factorial
+     100 factorial
+     1000 factorial
+     10000 factorial
+     100000 factorial
+     200000 factorial
+     300000 factorial
+     1000000 factorial
+
+     Time millisecondsToRun:[10000 factorial]40
+     Time millisecondsToRun:[100000 factorial]3220
+     Time millisecondsToRun:[1000000 factorial]357120
+
+    #(factorialIter factorialHalf factorialEvenOdd factorial)
+    do:[:sel |
+      #( (10000 10) 
+         (20000 10)
+         (50000 10)
+         (70000 10)
+         (100000 5)
+         (200000 3)
+         (300000 3)
+         (400000 3)) pairsDo:[:n :repeat |
+         |times|
+        times := (1 to:repeat) collect:[:i |
+                Time millisecondsToRun:[ n perform:sel]
+               ].
+
+        Transcript printf:'%12s %6d: %5d\n' with:sel with:n with:times min 
+      ]
+    ].
+
+    factorialIter  10000:    30
+    factorialIter  20000:   130
+    factorialIter  50000:   790
+    factorialIter  70000:  1710
+    factorialIter 100000:  4880
+    factorialIter 200000: 24980
+    factorialIter 300000: 60060
+    factorialIter 400000: 112310
+    factorialHalf  10000:    20
+    factorialHalf  20000:   100
+    factorialHalf  50000:   690
+    factorialHalf  70000:  1430
+    factorialHalf 100000:  3220
+    factorialHalf 200000: 28340
+    factorialHalf 300000: 68740
+    factorialHalf 400000: 127490
+    factorialEvenOdd  10000:    10
+    factorialEvenOdd  20000:    60
+    factorialEvenOdd  50000:   390
+    factorialEvenOdd  70000:   810
+    factorialEvenOdd 100000:  2020
+    factorialEvenOdd 200000:  9960
+    factorialEvenOdd 300000: 24480
+    factorialEvenOdd 400000: 45340
+    factorial  10000:    20
+    factorial  20000:   100
+    factorial  50000:   680
+    factorial  70000:  1400
+    factorial 100000:  2040
+    factorial 200000: 10130
+    factorial 300000: 24670
+    "
+!
+
+factorialEvenOdd
+    "an recursive odd-even algorithm, which processes smaller largeInts in the loop."
+
+    |pO i s2 t stop|
+
+    (self <= 20) ifTrue:[
+        ^ #(1 1 2 6 24 120 720 5040 40320 362880 3628800 39916800
+          479001600 6227020800 87178291200 1307674368000 20922789888000 
+          355687428096000 6402373705728000 121645100408832000
+          2432902008176640000) at:self+1
     ].
+
+    "/
+    "/ 3 * 4 * 5 * 6 *7 * 8 .... * n
+    "/ odd numbers:
+    "/   3 5 7 9 ... n
+    "/ half even:
+    "/   2 4 6 8 ... n
+    "/   1 2 3 4 ... n//2
+    "/ is (n/2)!! << n-1
+                 
+    pO := 1.
+    i := 3.
+ 
+    "/ odds only in pairs as
+    "/      i * (i + 2)
+    "/ to get to the next pair,
+    "/      (i+4)(i+6)
+    "/ we add: 8i + 24
+    "/ (i+4)(i+6)-(i*(i+2))
+    "/ i^2 + 10i + 24 - i^2 - 2i
+    "/ 8i + 24
+    stop := self-2.
+    t := i*(i+2).
+    [i <= stop] whileTrue:[
+        "/ odd*next odd
+        pO := pO * t.
+        t := t + ((i*8) + 24).
+        i := i + 4.
+    ].
+    
+    [i <= self] whileTrue:[
+        "/ odd
+        pO := pO * i.
+        i := i + 2.
+    ].
+
+    "/ the factorial of the evens...
+    s2 := (self//2).
+    ^ (s2 factorialEvenOdd * pO) << s2.
+
+    "
+     (6 to:2000) conform:[:i | i factorialIter = i factorialEvenOdd]
+     
+     Time millisecondsToRun:[20000 factorialIter]
+     Time millisecondsToRun:[50000 factorialIter]
+     Time millisecondsToRun:[70000 factorialIter]
+     Time millisecondsToRun:[100000 factorialIter]
+     Time millisecondsToRun:[200000 factorialIter] 
+
+     Time millisecondsToRun:[20000 factorialEvenOdd]
+     Time millisecondsToRun:[50000 factorialEvenOdd]
+     Time millisecondsToRun:[70000 factorialEvenOdd]
+     Time millisecondsToRun:[100000 factorialEvenOdd]
+     Time millisecondsToRun:[200000 factorialEvenOdd]
+    "
+!
+
+factorialHalf
+    "an algorithm, which processes does it with half the number of multiplications.
+     this is faster than factorialPM to roughly 60000."
+
+    |p i d|
+
+    i := self.
+    self odd ifTrue:[
+        i := i - 1.
+    ].
+    
+    p := i.
+    d := i - 2.
+    [d >= 2] whileTrue:[
+        i := i + d.
+        p := p * i.
+        d := d - 2.
+    ].
+    self odd ifTrue:[
+        p := p * self
+    ].    
+    ^ p
+
+    "
+     10 factorial 3628800
+     10 factorialHalf 3628800
+     
+     11 factorial 39916800
+     11 factorialHalf 39916800
+
+     12 factorial 479001600
+     12 factorialHalf 479001600 
+
+     10000 factorial = 10000 factorialHalf
+
+     (6 to:2000) conform:[:i | i factorialIter = i factorialHalf]
+     
+     Time microsecondsToRun:[30 factorialIter]
+     Time microsecondsToRun:[30 factorialHalf]
+     Time microsecondsToRun:[50 factorialIter]
+     Time microsecondsToRun:[50 factorialHalf]
+     Time microsecondsToRun:[75 factorialIter]
+     Time microsecondsToRun:[75 factorialHalf]
+     Time microsecondsToRun:[100 factorialIter]
+     Time microsecondsToRun:[100 factorialHalf]
+     Time microsecondsToRun:[500 factorialIter]
+     Time microsecondsToRun:[500 factorialHalf]
+     Time microsecondsToRun:[1000 factorialIter]
+     Time microsecondsToRun:[1000 factorialHalf]
+     Time microsecondsToRun:[2000 factorialIter]
+     Time microsecondsToRun:[2000 factorialHalf]
+
+     Time microsecondsToRun:[500 factorial]118 120 120
+     Time microsecondsToRun:[1000 factorial]339 355 406
+     Time microsecondsToRun:[5000 factorial]15703 13669 7715
+     Time millisecondsToRun:[10000 factorial]40 30 50
+     Time millisecondsToRun:[20000 factorial]140 150 150
+     Time millisecondsToRun:[40000 factorial]600 570 560 570
+     Time millisecondsToRun:[60000 factorial]1220 1240 1340
+     Time millisecondsToRun:[80000 factorial]2600 2580 2540
+     Time millisecondsToRun:[100000 factorial]4680 4810 5280
+     Time millisecondsToRun:[120000 factorial]8100 8010 7920
+     Time millisecondsToRun:[150000 factorial]13830 14040 13360
+     Time millisecondsToRun:[200000 factorial]23880 23740 
+
+     Time microsecondsToRun:[500 factorialHalf]150 142 192
+     Time microsecondsToRun:[1000 factorialHalf]383 527 684
+     Time microsecondsToRun:[5000 factorialHalf]6654 9221 4629
+     Time millisecondsToRun:[10000 factorialHalf]20 30 20
+     Time millisecondsToRun:[20000 factorialHalf]110 110 110
+     Time millisecondsToRun:[40000 factorialHalf]490 490 490
+     Time millisecondsToRun:[60000 factorialHalf]1100 1090 1070
+     Time millisecondsToRun:[80000 factorialHalf]1920 1920 1880
+     Time millisecondsToRun:[100000 factorialHalf]3030 3010 3000
+     Time millisecondsToRun:[120000 factorialHalf]4830 4770 4760
+     Time millisecondsToRun:[150000 factorialHalf]14510 13940 13900
+     Time millisecondsToRun:[200000 factorialHalf]28730 28160 
+    "
+!
+
+factorialIter
+    "return fac(self) (i.e. 1*2*3...*self) using an iterative algorithm.
+     This is slightly faster than the recursive algorithm, and does not
+     suffer from stack overflow problems (with big receivers)"
+
+    |p i|
+
     p := 2.
     i := 3.
     [i <= self] whileTrue:[
@@ -3077,7 +3307,7 @@
     "return fac(self) (i.e. 1*2*3...*self) using a recursive algorithm.
 
      This is included to demonstration purposes - if you really need
-     factorial numbers, use the iterative #factorial, which is slightly
+     factorial numbers, use the iterative #factorial, which is
      faster and does not suffer from stack overflow problems (with big receivers)."
 
     (self >= 2) ifTrue:[
@@ -3904,17 +4134,10 @@
         r := r4*base.    "/ radix^5 (chunks of 5 digits)
         nD := 5.
     ].
-
-    "/ JV@2015-12-28: I have to admit I don't understand this code,
-    "/ however, the following if made printing with base of 16 to
-    "/ diverge on 64bit builds (causing RegressionTests::IntegerTest>>testLargeIntegerHelpers
-    "/ to fail). When disabled, everything seems to be OK.
-    "/ Therefore I disabled the code, even though it might slower.
-
-"/    SmallInteger maxBits >= 63 ifTrue:[
-"/        r := r*r.    "/ radix^10 / radix^12 (chunks of 10/12 digits)
-"/        nD := nD * 2.
-"/    ].
+    SmallInteger maxBits >= 63 ifTrue:[
+        r := r*r2.    "/ radix^7 (chunks of 6 digits)
+        nD := nD + 2.
+    ].
 
     "get a Stream with space for the digits we are going to print.
      We need ((num log:base) ceiling) digits, which is equivalent
@@ -3956,7 +4179,8 @@
         31 printOn:Transcript base:2
         -20  printOn:Transcript base:16
         -20  printOn:Transcript base:10
-        Time millisecondsToRun:[10000 factorial printString] 610  7650
+        Time millisecondsToRun:[10000 factorial printString]
+        '%012d' printf:{  (2 raisedTo:20) }
     "
 
     "Modified: / 20-01-1998 / 18:05:02 / stefan"
--- a/LargeInteger.st	Mon Feb 08 06:59:19 2016 +0100
+++ b/LargeInteger.st	Thu Feb 11 16:21:50 2016 +0000
@@ -314,6 +314,8 @@
     "Modified: / 8.5.1998 / 21:40:41 / cg"
 ! !
 
+
+
 !LargeInteger class methodsFor:'queries'!
 
 isBuiltInClass
@@ -2397,7 +2399,7 @@
 
     num := anInteger abs.
     SmallInteger maxBytes == 8 ifTrue:[
-        (num > 16rFFFFFFFF) ifTrue:[
+        (num > 16rFFFFFFFFFF) ifTrue:[
             "if num is too big (so that multiplying by a byte could create a Large)"
             ^ anInteger retry:#* coercing:self
         ].
--- a/SHA1Stream.st	Mon Feb 08 06:59:19 2016 +0100
+++ b/SHA1Stream.st	Thu Feb 11 16:21:50 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 HashStream subclass:#SHA1Stream
 	instanceVariableNames:'hashContext'
 	classVariableNames:'HashSize ContextSize'
@@ -340,7 +342,7 @@
 "
     Test Vectors (from FIPS PUB 180-1); results are:
 
-								[exBegin]
+                                                                [exBegin]
     |hashStream|
 
     hashStream := SHA1Stream new.
@@ -348,16 +350,23 @@
     hashStream hashValue printOn:Transcript base:16. Transcript cr.
     hashStream nextPut:'dbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'.
     hashStream hashValue printOn:Transcript base:16. Transcript cr.
-								[exEnd]
+                                                                [exEnd]
+
+                                                                [exBegin]
+    |hashValue|
 
-								[exBegin]
+    hashValue := SHA1Stream hashValueOf:'hello world'.
+    self assert:(hashValue hexPrintString = '2AAE6C35C94FCFB415DBE95F408B9CE91EE846ED')
+                                                                [exEnd]
+                                                                
+                                                                [exBegin]
     |hashValue|
 
     hashValue := SHA1Stream hashValueOf:'abc'.
     hashValue printOn:Transcript base:16. Transcript cr.
-								[exEnd]
+                                                                [exEnd]
 
-								[exBegin]
+                                                                [exBegin]
     |hashStream|
 
     hashStream := SHA1Stream new.
@@ -366,47 +375,47 @@
     hashStream nextPut:'dbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq' asByteArray.
     hashStream hashValue printOn:Transcript base:16. Transcript cr.
 
-								[exEnd]
+                                                                [exEnd]
 
-								[exBegin]
+                                                                [exBegin]
     |hashStream|
 
     hashStream := SHA1Stream new.
     1000000 timesRepeat:[ hashStream nextPut:$a ].
     hashStream hashValue printOn:Transcript base:16. Transcript cr.
-								[exEnd]
+                                                                [exEnd]
 
-								[exBegin]
+                                                                [exBegin]
     |hashStream|
 
     hashStream := SHA1Stream new.
     hashStream nextPut:'a'.
     hashStream hashValue printOn:Transcript base:16. Transcript cr.
-								[exEnd]
+                                                                [exEnd]
 
-								[exBegin]
+                                                                [exBegin]
     |hashStream|
 
     hashStream := SHA1Stream new.
     hashStream nextPut:$a.
     hashStream hashValue printOn:Transcript base:16. Transcript cr.
-								[exEnd]
+                                                                [exEnd]
 
   timing throughput:
-								[exBegin]
+                                                                [exBegin]
     |hashStream n t|
 
     hashStream := SHA1Stream new.
     n := 1000000.
     t := Time millisecondsToRun:[
-	    n timesRepeat:[
-		hashStream nextPutAll:'12345678901234567890123456789012345678901234567890'.
-	    ].
-	 ].
+            n timesRepeat:[
+                hashStream nextPutAll:'12345678901234567890123456789012345678901234567890'.
+            ].
+         ].
     t := (t / 1000) asFloat.
     Transcript show:t; show:' seconds for '; show:(50*n/1024) asFloat; showCR:' Kb'.
     Transcript show:(n*50/1024 / t); showCR:' Kb/s'
-								[exEnd]
+                                                                [exEnd]
 "
 !