Integer.st
branchjv
changeset 19103 71257a47eba2
parent 19065 1fc3abdcb8f9
parent 19089 82c431661f59
child 19104 e7c5169d9ab7
--- a/Integer.st	Thu Jan 21 17:58:19 2016 +0000
+++ b/Integer.st	Sat Jan 23 07:23:05 2016 +0000
@@ -70,7 +70,7 @@
 byte1:b1 byte2:b2 byte3:b3 byte4:b4
     "Squeak compatibility:
      Return an Integer given four value bytes.
-     The returned integer is either a Small- or a LargeInteger 
+     The returned integer is either a Small- or a LargeInteger
      (on 32bit systems - on 64bit systems, it will be always a SmallInteger)"
 
     |t|
@@ -223,7 +223,7 @@
      negative specifies if the result should be a negative number.
      The digits can be stored byte-wise into the result, using digitAt:put:"
 
-    ^ LargeInteger basicNew 
+    ^ LargeInteger basicNew
             numberOfDigits:numberOfBytes
             sign:(negative ifTrue:[-1] ifFalse:[1])
 !
@@ -926,7 +926,7 @@
 
 primeCacheSize
     "see comment in initializePrimeCacheUpTo:limit"
-    
+
     ^ PrimeCache size * 2
 
     "
@@ -1057,7 +1057,7 @@
 primesUpTo: max do: aBlock
     "Compute aBlock with all prime integers up to and including the given integer.
      See comment in initializePrimeCacheUpTo:limit"
-     
+
     | limit flags prime k |
 
     max <= 2000 ifTrue:[
@@ -1126,7 +1126,7 @@
 !Integer methodsFor:'*Roe'!
 
 acceptRoeVisitor: aVisitor
-	^ aVisitor visitInteger: self
+        ^ aVisitor visitInteger: self
 ! !
 
 !Integer methodsFor:'Compatibility-Dolphin'!
@@ -1134,7 +1134,7 @@
 & aNumber
     "return the bitwise-and of the receiver and the argument, anInteger.
      Same as bitAnd: - added for compatibility with Dolphin Smalltalk.
-     Notice: 
+     Notice:
         please do not use ^ for integers in new code; it makes the code harder
         to understand, as it may be not obvious, whether a boolean or a bitWise or is intended.
         For integers, use bitAnd: to make the intention explicit."
@@ -1228,7 +1228,7 @@
 | aNumber
     "return the bitwise-or of the receiver and the argument, anInteger.
      Same as bitOr: - added for compatibility with Dolphin Smalltalk.
-     Notice: 
+     Notice:
         please do not use | for integers in new code; it makes the code harder
         to understand, as it may be not obvious, whether a boolean or a bitWise or is intended.
         For integers, use bitOr: to make the intention explicit."
@@ -1256,7 +1256,7 @@
     "return my hexBytes in MSB, optionally padded at the left with zeros"
 
     "(((
-        | repeats number | 
+        | repeats number |
         repeats := 1000000.
         number := 123456789123456789123456789123456789123456789123456789.
          [repeats timesRepeat: (number asByteArrayOfSize: 1024) ] timeToRun.
@@ -1279,7 +1279,7 @@
 
      255 asByteArrayOfSize:1 #[255]
 
-     256 asByteArrayOfSize:1 
+     256 asByteArrayOfSize:1
      256 asByteArrayOfSize:2
      256 asByteArrayOfSize:4
     "
@@ -1314,9 +1314,9 @@
     ^ (self printStringRadix:base) leftPaddedTo:size with:padChar
 
     "
-     1234 printPaddedWith:$0 to:4 base:16     
-     1234 printLeftPaddedWith:$0 to:4 base:16 
-     128 printLeftPaddedWith:$0 to:2 base:16  
+     1234 printPaddedWith:$0 to:4 base:16
+     1234 printLeftPaddedWith:$0 to:4 base:16
+     128 printLeftPaddedWith:$0 to:2 base:16
     "
 !
 
@@ -1526,8 +1526,9 @@
 !
 
 bitClear:aMaskInteger
-    "return the bitwise-and of the receiver and the complement of argument, anInteger,
+    "return the bitwise-and of the receiver and the complement of the argument, anInteger,
      returning the receiver with bits of the argument cleared.
+     (i.e. the same as self bitAnd:aMaskInteger bitInvert).
      This is a general and slow implementation, walking over the bytes of
      the receiver and the argument."
 
@@ -1598,11 +1599,24 @@
     ].
     ^ result
 
-     "
-      16rff bitInvert bitAnd:16rff
-      16rffffffff bitInvert
-      16rff00ff00 bitInvert hexPrintString
-     "
+    "
+     16rff bitInvert bitAnd:16rff
+     16rffffffff bitInvert
+     16rff00ff00 bitInvert hexPrintString
+    "
+!
+
+bitInvertByte
+    "return a new integer, where the low 8 bits are masked and complemented.
+     This returns an unsigned version of what bitInvert would return.
+     (i.e. same as self bitInvert bitAnd:16rFF)"
+
+    ^ (self digitAt:1) bitInvert bitAnd:16rFF
+    
+    "
+     16rff bitInvert
+     16rff bitInvertByte
+    "
 !
 
 bitOr:aMaskInteger
@@ -1877,7 +1891,7 @@
     ^ self bitOr:mask
 
     "
-     (16r3fffffff changeMask:16r80 to:0) hexPrintString 
+     (16r3fffffff changeMask:16r80 to:0) hexPrintString
      (16r3fff0000 changeMask:16r80 to:1) hexPrintString
     "
 !
@@ -2353,7 +2367,7 @@
         "ByteArray<<#swapBytes needs even number of bytes.
          Add 0 to the most significant position (the end)"
         digitBytes := digitBytes copyWith:0.
-        
+
     ].
     ^ (LargeInteger digitBytes:digitBytes swapBytes) compressed
 
@@ -2483,7 +2497,7 @@
      16r7FFFFF signExtended24BitValue
      16rFFFFFF signExtended24BitValue
     "
-    
+
     "Modified: / 07-05-1996 / 09:31:57 / cg"
     "Created: / 05-03-2012 / 14:37:55 / cg"
 !
@@ -2512,11 +2526,11 @@
      This may be useful for communication interfaces"
 
     |masked|
-    
+
     masked := self bitAnd:((1 bitShift:bitNr)-1).
     (self isBitSet:bitNr) ifTrue:[
         ^ masked - (1 bitShift:bitNr)
-    ].    
+    ].
     ^ masked
 
     "
@@ -2536,7 +2550,7 @@
 
     (self bitTest:16r8000000000000000) ifTrue:[
         ^ (self bitAnd:16rFFFFFFFFFFFFFFFF) - 16r10000000000000000
-    ].    
+    ].
     ^ (self bitAnd:16r7FFFFFFFFFFFFFFF)
 
     "
@@ -2554,7 +2568,7 @@
 
     (self bitTest:16r80000000) ifTrue:[
         ^ (self bitAnd:16rFFFFFFFF) - 16r100000000
-    ].    
+    ].
     ^ (self bitAnd:16r7FFFFFFF)
 
     "
@@ -2747,7 +2761,7 @@
 
     "
      1 to:10 collect:[:i | i squared]
-     10 to:20 collect:[:i | i squared]  
+     10 to:20 collect:[:i | i squared]
      (10 to:20) collect:[:i | i squared]
     "
 ! !
@@ -2838,14 +2852,14 @@
 !
 
 divMod:aNumber
-    "return an array filled with 
+    "return an array filled with
         (self // aNumber) and (self \\ aNumber).
      The returned remainder has the same sign as aNumber.
      The following is always true:
         (receiver // something) * something + (receiver \\ something) = receiver
 
      Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
-     Especially surprising:     
+     Especially surprising:
         -1 \\ 10 -> 9  (because -(1/10) is truncated towards next smaller integer, which is -1,
                         and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
         -10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
@@ -2861,7 +2875,7 @@
     "
      10 divMod:3       -> #(3 1)   because 3*3 + 1 = 10
      10 divMod:-3      -> #(-4 -2) because -4*-3 + (-2) = 10
-     -10 divMod:3      -> #(-4 2) because -4*-3 + 2 = -10   
+     -10 divMod:3      -> #(-4 2) because -4*-3 + 2 = -10
      -10 divMod:-3     -> #(3 -1)  because -3*3 + (-1) = -10
 
      1000000000000000000000 divMod:3   -> #(333333333333333333333 1)
@@ -3169,26 +3183,26 @@
     ^ self highBit - 1.
 
     "
-      2  log:2  
-      2  integerLog2  
-
-      3  log:2       
-      3  integerLog2  
-
-      4  log:2          
-      4  integerLog2    
-
-      64  integerLog2  
+      2  log:2
+      2  integerLog2
+
+      3  log:2
+      3  integerLog2
+
+      4  log:2
+      4  integerLog2
+
+      64  integerLog2
       100 integerLog2
       100 log:2
       999 integerLog2
       999 log:2
-      120000 integerLog2 
-      120000 log:2       
+      120000 integerLog2
+      120000 log:2
       -1 integerLog2
-      50 factorial integerLog2   
+      50 factorial integerLog2
       50 factorial log:2
-      1000 factorial integerLog2   
+      1000 factorial integerLog2
       1000 factorial log:2       -- float error!!
     "
 !
@@ -3229,7 +3243,7 @@
 
 integerSqrt
     "return the largest integer which is less or equal to the
-     receiver's square root. 
+     receiver's square root.
      This might be needed for some number theoretic problems with large numbers
      (and also in cryptography). Uses Newton's method"
 
@@ -3243,10 +3257,11 @@
             arguments:#()
             errorString:'bad (negative) receiver in sqrt'
     ].
+    self == 0 ifTrue:[^ 0].
     
     guess := (1 bitShift:(self highBit // 2)).
 
-    [ 
+    [
         prevGuess ~= guess
         and:[ ((guessSquared := guess squared) - self) abs >= guess ]
     ] whileTrue:[
@@ -3262,14 +3277,14 @@
     ^ guess.
 
     "
-     333 integerSqrt          
-     325 integerSqrt          
-     324 integerSqrt          
-     323 integerSqrt          
+     333 integerSqrt
+     325 integerSqrt
+     324 integerSqrt
+     323 integerSqrt
      10239552311579 integerSqrt
      5397346292805549782720214077673687806275517530364350655459511599582614290 integerSqrt
      1000 factorial integerSqrt
-     
+
      1000 factorial - 1000 factorial integerSqrt squared
      1000 factorial - (1000 factorial integerSqrt + 1) squared
    "
@@ -3673,12 +3688,12 @@
 
     "
      (100 factorial) asBCD
-     999999999 asBCD 
-     100000000 asBCD   
-     123456789 asBCD   
-     99999999 asBCD  
+     999999999 asBCD
+     100000000 asBCD
+     123456789 asBCD
+     99999999 asBCD
      12345678 asBCD
-     12345678 asBCD 
+     12345678 asBCD
      12345678 asBCD hexPrintString
      12345678901234567890 asBCD
     "
@@ -3713,7 +3728,7 @@
     ^ s contents reverse
 
     "
-     12345678 asBCDBytes 
+     12345678 asBCDBytes
      12345678 asBCDBytes hexPrintString
      12345678901234567890 asBCDBytes
     "
@@ -3823,7 +3838,7 @@
 "/        r := r*r.    "/ radix^10 / radix^12 (chunks of 10/12 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
      to ((num log:2)/(base log:2) ceiling)
@@ -3847,7 +3862,7 @@
         ].
     ].
 
-    [num ~= 0] whileTrue:[
+    [num ~~ 0] whileTrue:[
         divMod := num divMod:base.
         num := divMod at:1.
         mod := divMod at:2.
@@ -3873,7 +3888,7 @@
     "Modified (comment): / 28-12-2015 / 08:23:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-printOn:aStream base:baseInteger size:sz 
+printOn:aStream base:baseInteger size:sz
     "print a string representation of the receiver in the specified
      base. The string is padded on the left with fillCharacter to make
      its size as specified in sz."
@@ -4035,7 +4050,7 @@
     ^ self printStringRadix:base showRadix:false
 
     "
-     10 printStringRadix:16   
+     10 printStringRadix:16
     "
 
     "Created: / 19-01-1998 / 17:20:58 / stefan"
@@ -4141,17 +4156,17 @@
 
     "
      self assert:( 1.0 exponent = 1 exponent ).
-     self assert:( 2.0 exponent = 2 exponent ).  
-     self assert:( 3.0 exponent = 3 exponent ).  
-     self assert:( 4.0 exponent = 4 exponent ).  
-     self assert:( 12345.0 exponent = 12345 exponent ).  
-     self assert:( 0.0 exponent = 0 exponent ).   
+     self assert:( 2.0 exponent = 2 exponent ).
+     self assert:( 3.0 exponent = 3 exponent ).
+     self assert:( 4.0 exponent = 4 exponent ).
+     self assert:( 12345.0 exponent = 12345 exponent ).
+     self assert:( 0.0 exponent = 0 exponent ).
 
      self assert:( -1.0 exponent = -1 exponent ).
-     self assert:( -2.0 exponent = -2 exponent ).  
-     self assert:( -3.0 exponent = -3 exponent ).  
-     self assert:( -4.0 exponent = -4 exponent ).  
-     self assert:( -12345.0 exponent = -12345 exponent ).  
+     self assert:( -2.0 exponent = -2 exponent ).
+     self assert:( -3.0 exponent = -3 exponent ).
+     self assert:( -4.0 exponent = -4 exponent ).
+     self assert:( -12345.0 exponent = -12345 exponent ).
     "
 !
 
@@ -4171,9 +4186,9 @@
 isPerfectSquare
     "return true if I am a perfect square.
      That is a number for which the square root is an integer."
-     
+
     |intSqrt realSqrt|
-    
+
     self strictlyPositive ifFalse:[
         self == 0 ifTrue:[^ true].
         "/ should we raise a domain error for negative receivers?
@@ -4181,18 +4196,18 @@
     ].
 
     "/ q&d check for common small squares
-    self < 400 ifTrue:[    
+    self < 400 ifTrue:[
         ^ #(1 4 9 16 25 36 49 64 81 100 121 144 169 196 225 256 289 324 361 ) includes:self.
-    ].        
-    self < 1024 ifTrue:[    
+    ].
+    self < 1024 ifTrue:[
         ^ #(400 441 484 529 576 625 676 729 784 841 900 961) includes:self.
     ].
-    
+
     "/ try powers of 2
     self isPowerOfTwo ifTrue:[
         ^ self lowBit odd
     ].
-    
+
     "/ guess
     realSqrt := self sqrt.
     realSqrt isFinite ifTrue:[
@@ -4200,9 +4215,9 @@
             "/ still have to check due to rounding errors.
             intSqrt := realSqrt truncated asInteger.
             ^ intSqrt squared = self
-        ].    
+        ].
     ].
-    
+
     "/ slow code
     intSqrt := self integerSqrt.
     ^ intSqrt squared = self
@@ -4236,7 +4251,7 @@
     "
      0 isPowerOf:2
      1 isPowerOf:2
-     
+
      16r0000000000000000 isPowerOf:2
      16r0000004000000000 isPowerOf:2
      16r0000004000000001 isPowerOf:2
@@ -4287,12 +4302,12 @@
     ^ true
 
     "
-     10000 factorial isPowerOfTwo  
-     |n| n := 10000 factorial. Time millisecondsToRun:[1000 timesRepeat:[ n isPowerOfTwo]] 
-    "
-    "
-     (2 raisedTo:10000) isPowerOfTwo  
-     |n| n := (2 raisedTo:10000). Time millisecondsToRun:[1000 timesRepeat:[ n isPowerOfTwo]] 
+     10000 factorial isPowerOfTwo
+     |n| n := 10000 factorial. Time millisecondsToRun:[1000 timesRepeat:[ n isPowerOfTwo]]
+    "
+    "
+     (2 raisedTo:10000) isPowerOfTwo
+     |n| n := (2 raisedTo:10000). Time millisecondsToRun:[1000 timesRepeat:[ n isPowerOfTwo]]
     "
 
     "Modified: / 20-06-2011 / 12:43:05 / cg"
@@ -4353,13 +4368,13 @@
     ^ self + (n - rest)
 
     "
-     1 nextMultipleOf: 4  
-     2 nextMultipleOf: 4  
-     3 nextMultipleOf: 4  
-     4 nextMultipleOf: 4  
-     5 nextMultipleOf: 4  
-
-     22 nextMultipleOf: 4 
+     1 nextMultipleOf: 4
+     2 nextMultipleOf: 4
+     3 nextMultipleOf: 4
+     4 nextMultipleOf: 4
+     5 nextMultipleOf: 4
+
+     22 nextMultipleOf: 4
     "
 !
 
@@ -4367,7 +4382,7 @@
     "return the power of 2 at or above the receiver.
      Useful for padding.
      Notice, that for a powerOf2, the receiver is returned.
-     Also notice, that (because it is used for padding), 
+     Also notice, that (because it is used for padding),
      0 is returned for zero."
 
     |x t sh|
@@ -4382,33 +4397,33 @@
         sh := -32.
         [
             x := x bitOr: (t := x bitShift: sh).
-            sh := sh + sh. 
+            sh := sh + sh.
         ] doWhile: [t ~~ 0]
     ].
-    ^ x + 1 
-
-    "
-     0 nextPowerOf2    
-     1 nextPowerOf2    
-     2 nextPowerOf2    
-     3 nextPowerOf2    
-     4 nextPowerOf2    
-     5 nextPowerOf2    
-     6 nextPowerOf2    
-     7 nextPowerOf2    
-     8 nextPowerOf2    
+    ^ x + 1
+
+    "
+     0 nextPowerOf2
+     1 nextPowerOf2
+     2 nextPowerOf2
+     3 nextPowerOf2
+     4 nextPowerOf2
+     5 nextPowerOf2
+     6 nextPowerOf2
+     7 nextPowerOf2
+     8 nextPowerOf2
 
      22 nextPowerOf2
-     12 factorial nextPowerOf2  isPowerOf:2  
-     100 factorial nextPowerOf2  isPowerOf:2  
+     12 factorial nextPowerOf2  isPowerOf:2
+     100 factorial nextPowerOf2  isPowerOf:2
      1000 factorial nextPowerOf2  isPowerOf:2
      Time millisecondsToRun:[
          |v|
          v := 1000 factorial.
          1000 timesRepeat:[
-            v nextPowerOf2    
-         ]    
-     ]    
+            v nextPowerOf2
+         ]
+     ]
     "
 !
 
@@ -4447,14 +4462,14 @@
     ^ self bitCount odd
 
     "
-     0 parityOdd    
-     1 parityOdd    
-     2 parityOdd    
-     4 parityOdd    
-     5 parityOdd    
-     7 parityOdd    
-     33 parityOdd   
-     6 parityOdd    
+     0 parityOdd
+     1 parityOdd
+     2 parityOdd
+     4 parityOdd
+     5 parityOdd
+     7 parityOdd
+     33 parityOdd
+     6 parityOdd
 
      1 to:1000000 do:[:n |
         self assert:(n parityOdd = ((n printStringRadix:2) occurrencesOf:$1) odd).
@@ -4463,9 +4478,9 @@
      0 to:255 do:[:n |
         |p|
 
-        p := 
-            (((((((((n rightShift: 7) 
-            bitXor: (n rightShift: 6)) 
+        p :=
+            (((((((((n rightShift: 7)
+            bitXor: (n rightShift: 6))
                 bitXor: (n rightShift: 5))
                     bitXor: (n rightShift: 4))
                         bitXor: (n rightShift: 3))
@@ -4482,7 +4497,7 @@
 !Integer methodsFor:'special modulo arithmetic'!
 
 add_32:anInteger
-    "return a C-semantic 32bit sum of the receiver and the argument. 
+    "return a C-semantic 32bit sum of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns a signed 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4512,7 +4527,7 @@
 !
 
 add_32u:anInteger
-    "return a C-semantic 32bit unsigned sum of the receiver and the argument. 
+    "return a C-semantic 32bit unsigned sum of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns an unsigned 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4542,7 +4557,7 @@
 !
 
 mul_32:anInteger
-    "return a C-semantic 32bit product of the receiver and the argument. 
+    "return a C-semantic 32bit product of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns a signed 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4572,7 +4587,7 @@
 !
 
 mul_32u:anInteger
-    "return a C-semantic 32bit unsigned product of the receiver and the argument. 
+    "return a C-semantic 32bit unsigned product of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns an unsigned 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4602,7 +4617,7 @@
 !
 
 sub_32:anInteger
-    "return a C-semantic 32bit difference of the receiver and the argument. 
+    "return a C-semantic 32bit difference of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns a signed 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of
@@ -4632,7 +4647,7 @@
 !
 
 sub_32u:anInteger
-    "return a C-semantic 32bit unsigned difference of the receiver and the argument. 
+    "return a C-semantic 32bit unsigned difference of the receiver and the argument.
      Both must be either Small- or LargeIntegers.
      Returns an unsigned 32bit number.
      This (nonstandard) specialized method is provided to allow simulation of