Integer.st
author claus
Sat, 02 Sep 1995 18:08:30 +0200
changeset 420 081f7b2bb3b3
parent 384 cc3d110ea879
child 487 898ed6e7391c
permissions -rw-r--r--
Initial revision

"
 COPYRIGHT (c) 1988 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.
"

Number subclass:#Integer
       instanceVariableNames:''
       classVariableNames:'DefaultDisplayRadix'
       poolDictionaries:''
       category:'Magnitude-Numbers'
!

Integer comment:'
COPYRIGHT (c) 1988 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.31 1995-08-11 03:01:15 claus Exp $
'!

!Integer class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1988 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.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.31 1995-08-11 03:01:15 claus Exp $
"
!

documentation
"
    abstract superclass for all integer numbers.
    See details in concrete subclasses LargeInteger and SmallInteger.

    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.

"
! !

!Integer class methodsFor:'constants'!

zero
    "return the neutral element for addition"

    ^ 0
!

unity
    "return the neutral element for multiplication"

    ^ 1
! !

!Integer class methodsFor:'instance creation'!

new:numberOfBytes neg:negative
    "for ST-80 compatibility:
     Return an empty Integer (uninitialized value) with space for
     numberOfBytes bytes (= digitLength). The additional argument
     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 numberOfDigits:numberOfBytes) 
		sign:(negative ifTrue:[-1] ifFalse:[1])
! !

!Integer class methodsFor:'misc'!

displayRadix:aNumber
    "being tired of always sending #printStringRadix: in the inspectors,
     this allows you to change the default print radix for the displayString
     method."

    DefaultDisplayRadix := aNumber

    "
     Integer displayRadix:16. 123456 inspect
     Integer displayRadix:10. 123456 inspect
    "
! !

!Integer methodsFor:'arithmetic'!

quo:aNumber
    "Return the integer quotient of dividing the receiver by aNumber with
     truncation towards zero. For Integers this is same as //"

    ^ self // aNumber

! !

!Integer methodsFor:'double dispatching'!

sumFromFraction:aFraction
    "sent when a fraction does not know how to add the receiver, an integer"

    |d|

    d := aFraction denominator.
    ^ (Fraction numerator:(aFraction numerator + (self * d))
	      denominator:d) reduced
!

differenceFromFraction:aFraction
    "sent when a fraction does not know how to subtract the receiver, an integer"

    |d|

    d := aFraction denominator.
    ^ (Fraction numerator:(aFraction numerator - (self * d))
	      denominator:d) reduced
!

productFromFraction:aFraction
    "sent when a fraction does not know how to multiply the receiver, an integer"

    ^ (Fraction numerator:(self * aFraction numerator)
	      denominator:aFraction denominator) reduced
!

quotientFromFraction:aFraction
    "sent when a fraction does not know how to divide the receiver, an integer"

    ^ (Fraction numerator:aFraction numerator
	      denominator:(self * aFraction denominator)) reduced
! !

!Integer methodsFor:'bit operators'!

bitAnd:anInteger
    "return the bitwise-and of the receiver and the argument, anInteger.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |result n byte|

    n := (anInteger digitLength) min:(self digitLength).
    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 == 0 or:[n < 5]) ifTrue:[
	^ result normalize
    ].
    ^ result

    "
     (16r112233445566778899 bitAnd:16rFF                ) printStringRadix:16 
     (16r112233445566778899 bitAnd:16rFFFFFFFFFFFFFFFF00) printStringRadix:16 
     (16r112233445566778899 bitAnd:16rFF0000000000000000) printStringRadix:16 
     (16r112233445566778899 bitAnd:16r00000000000000FFFF) printStringRadix:16 
    "
!

bitOr:anInteger
    "return the bitwise-or of the receiver and the argument, anInteger.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |result n byte|

    n := (anInteger digitLength) max:(self digitLength).
    result := self class basicNew numberOfDigits:n.

    1 to:n do:[:index |
	byte := (anInteger digitAt:index) bitOr:(self digitAt:index).
	result digitAt:index put:byte.
    ].
"/ no need to normalize - if the operands were correct
"/    byte == 0 ifTrue:[
"/        ^ result normalize
"/    ].
    ^ result
!

bitXor:anInteger
    "return the bitwise-or of the receiver and the argument, anInteger.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |result n byte|

    n := (anInteger digitLength) max:(self digitLength).
    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 == 0 ifTrue:[
	^ result normalize
    ].
    ^ result

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

highBit
    "return the bitIndex of the highest bit set. The returned bitIndex
     starts at 1 for the least significant bit. Returns -1 if no bit is set."

    |byteNr highByte|

    byteNr := self digitLength.
    highByte := self digitAt:byteNr.
    ^ (byteNr - 1) * 8 + highByte highBit

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

bitAt:index
    "return the value of the index's bit (index starts at 1).
     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)"

    |i "{Class: SmallInteger}"|

    i := index - 1.
    ^ (self digitAt:(i // 8 + 1)) bitAt:(i \\ 8 + 1)

    "
     1 bitAt:1                  
     (1 bitShift:30) bitAt:30    
     (1 bitShift:30) bitAt:31    
     (1 bitShift:30) bitAt:32    
     (1 bitShift:31) bitAt:31    
     (1 bitShift:31) bitAt:32    
     (1 bitShift:31) bitAt:33    
     (1 bitShift:32) bitAt:32    
     (1 bitShift:32) bitAt:33    
     (1 bitShift:32) bitAt:34    
     (1 bitShift:64) bitAt:64     
     (1 bitShift:64) bitAt:65     
     (1 bitShift:64) bitAt:66     
     (1 bitShift:1000) bitAt:1000   
     (1 bitShift:1000) bitAt:1001  
     (1 bitShift:1000) bitAt:1002 
     (1 bitShift:1000) bitAt:2000  
    "
!

bitShift:shiftCount
    "return the value of the receiver shifted by shiftCount bits;
     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)"

    |result 
     prev       "{ Class: SmallInteger }"
     next       "{ Class: SmallInteger }"
     byte       "{ Class: SmallInteger }"
     byte2      "{ Class: SmallInteger }"
     bitShift   "{ Class: SmallInteger }"
     revShift   "{ Class: SmallInteger }"
     digitShift "{ Class: SmallInteger }"
     n          "{ Class: SmallInteger }" 
     nn         "{ Class: SmallInteger }"|

    shiftCount > 0 ifTrue:[
	"left shift"

	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
	].

	"
	 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 normalize
	    ].
	    ^ 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.
	2 to:(self digitLength) do:[:index |
	    byte := self digitAt:index.
	    byte2 := self digitAt:index-1.
	    byte := byte bitShift:bitShift.
	    byte2 := byte2 bitShift:revShift.
	    byte := byte bitOr:byte2.
	    byte := byte bitAnd:16rFF.
	    result digitAt:(index + digitShift) put:byte.
	].
	byte2 := self digitAt:self digitLength.
	byte2 := byte2 bitShift:revShift.
	byte2 := byte2 bitAnd:16rFF.
	result digitAt:(self digitLength + digitShift + 1) put:byte2.
	"
	 might have stored a 0-byte ...
	"
	byte2 == 0 ifTrue:[
	    ^ result normalize
	].
	^ result
    ].

    shiftCount < 0 ifTrue:[
	"right shift"

	digitShift := shiftCount negated // 8.
	bitShift := shiftCount negated \\ 8.
	n := self digitLength.

	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 normalize
	    ].
	    ^ 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 normalize
	    ].
	    ^ result
	].

	"
	 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 normalize
    ].

    ^ self "no shift"
! !

!Integer methodsFor:'truncation & rounding'!

ceiling
    "I am my ceiling"

    ^ self
!

floor
    "I am my floor"

    ^ self
!

rounded
    "return the receiver rounded toward the next Integer -
     for integers this is self"

    ^ self
!

truncated
    "return the receiver truncated towards zero - 
     for integers this is self"

    ^ self
!

normalize
    "this is ST/X's name for ST-80's compressed.
     ST/X may be changed for full compatibility."

    ^ self
!

compressed
    "this is ST-80's name for ST/X's normalize.
     ST/X may be changed for full compatibility."

    ^ self normalize
! !

!Integer methodsFor:'queries'!

digitLength
    "return the number of bytes needed for the binary representation
     of the receiver"

    ^ (self log:256) ceiling asInteger
!

digitAt:n
    "return the n-th byte of the binary representation.
     This is a very stupid implementation, and should be redefined in
     concrete subclasses."

    |num count|

    num := self.
    count := n.
    [count > 1] whileTrue:[
	num := num // 256.
	count := count - 1
    ].
    ^ num \\ 256

    "
     16r44332211 digitAt:1     
     16r44332211 digitAt:2    
     16r44332211 digitAt:3     
     16r44332211 digitAt:4     
     16r44332211 digitAt:5     
     16r00332211 digitAt:4     
     16r00332211 digitAt:5     
    "
!

isInteger
    "return true, if the receiver is some kind of integer number"

    ^ true
! !

!Integer methodsFor:'misc math'!

factorial
    "return 1*2*3...*self"

    (self >= 2) ifTrue:[
	^ self * (self - 1) factorial
    ].
    ^ 1

    "
     10 factorial
     1000 factorial
    "
!

gcd:anInteger
    "return the greatest common divisor (Euclid's algorithm)"

    |ttt selfInteger temp|

    ttt := anInteger.
    selfInteger := self.
    [ttt ~~ 0] whileTrue:[
	temp := selfInteger \\ ttt.
	selfInteger := ttt.
	ttt := temp
    ].
    ^ selfInteger

    "
     65 gcd:15
     3 gcd:15
     132 gcd:55
    "
!

lcm:anInteger
    "return the least common multiple (using gcd:)"

    ^ (self * anInteger) abs // (self gcd: anInteger)

    "
     65 lcm:15
     3 lcm:15
    "
!

fib
    "dont use this method if you need fibionacci numbers -
     this method is for benchmarking purposes only.
     (use fastFib instead and dont ever try 60 fib ...)"

    (self > 1) ifTrue:[
	^ (self - 1) fib + (self - 2) fib
    ].
    ^ 1

    "
    10 fib
    20 fib
    Transcript showCr:(Time millisecondsToRun:[30 fib])
    "

    "
     ds3100  486/50  Indy(no cache)
     20804    4800     2145
    "
!

fastFib
    "this method just to show how a changed algorithm can
     change things much more drastic than tuning ...
     (compare 30 fib with 30 fastFib / dont even try 60 fib)"

    ^ self fibUsingCache:(OrderedCollection new)

    "
     Transcript showCr:(Time millisecondsToRun:[30 fib]) 
     Transcript showCr:(Time millisecondsToRun:[30 fastFib]) 
     Transcript showCr:(Time millisecondsToRun:[60 fastFib])
     Transcript showCr:(Time millisecondsToRun:[200 fastFib])
    "
!

fibUsingCache:fibCache
    "actual fastfib worker; keep track of already computed fib
     numbers in fibCache, which is passed around. Take value from
     the cache if already present. Doing so, the double recursive
     fib actually becomes a single recursive algorithm."

    |fib|

    self <= 1 ifTrue:[^ 1].

    fibCache size >= self ifTrue:[
	^ fibCache at:self
    ].
    fib := ((self - 2) fibUsingCache:fibCache) + ((self - 1) fibUsingCache:fibCache).

    fibCache grow:self.
    fibCache at:self put:fib.
    ^ fib
!

acker:n
    "return the value of acker(self, n)"

    (self == 0) ifTrue:[^ n + 1].
    (n == 0) ifTrue:[^ (self - 1) acker: 1].
    ^ (self - 1) acker:(self acker:(n - 1))

    "
     3 acker:2  
    "
! !

!Integer methodsFor:'coercing and converting'!

asFraction
    "return a Fraction with same value as receiver"

    ^ Fraction numerator:self denominator:1
!

asInteger
    "return the receiver truncated towards zero - 
     for integers this is self"

    ^ self
! !

!Integer methodsFor:'printing & storing'!

printOn:aStream
    "append a printed description of the receiver to aStream"

    aStream nextPutAll:(self printStringRadix:10)
!

printOn:aStream radix:base
    "append a printed description of the receiver to aStream"

    aStream nextPutAll:(self printStringRadix:base)
!

printString
    "return a string representation of the receiver"

    ^ self printStringRadix:10
!

hexPrintString
    "return a hex string representation of the receiver"

    ^ self printStringRadix:16
!

displayString
    "return a string for displaying in a view (as in inspector).
     The output radix is usually 10, but can be changed by setting
     DefaultDisplayRadix (see Integer>>displayRadix:)"

    (DefaultDisplayRadix isNil or:[DefaultDisplayRadix == 10]) ifTrue:[
	^ self printString
    ].
    ^ self radixPrintStringRadix:DefaultDisplayRadix

    "
     Integer displayRadix:16. 12345 
     Integer displayRadix:2.  12345 
     Integer displayRadix:10. 12345
    "
!

radixPrintStringRadix:aRadix
    "return a string representation of the receiver in the specified
     radix; prepend XXr to the string"

    ^ (aRadix printString) , 'r', (self printStringRadix:aRadix)

    "
     31 radixPrintStringRadix:2
     31 radixPrintStringRadix:3
     31 radixPrintStringRadix:36
    "
!

printStringRadix:aRadix
    "return a string representation of the receiver in the specified
     radix (without the initial XXr)"

    |num s "rx leftPart"|

    (aRadix between:2 and:36) ifFalse:[
	self error:'invalid radix'.
	^ self printStringRadix:10
    ].

    (self = 0) ifTrue:[^ '0'].
    (self < 0) ifTrue:[
	^ '-' , (self negated printStringRadix:aRadix)
    ].

    "
     claus: changed it from a recursive algorithm;
     (it used to trigger stack-overflow exceptions when printing
      3000 factorial ...)
    "
"/    leftPart := self // aRadix.
"/    (leftPart ~= 0) ifTrue:[
"/        ^ (leftPart printStringRadix:aRadix) copyWith:(Character digitValue:(self \\ aRadix))
"/    ].
"/    ^ (Character digitValue:self) asString

    num := self.
    s := (Character digitValue:(num \\ aRadix)) asString.
    num := num // aRadix.
    [num ~= 0] whileTrue:[
	s := (Character digitValue:(num \\ aRadix)) asString , s.
	num := num // aRadix.
    ].
    ^ s
!

printStringRadix:aRadix size:sz fill:fillCharacter
    "return a string representation of the receiver in the specified
     radix. The string is padded on the left with fillCharacter to make
     its size as specified in sz."

    |s|

    s := self printStringRadix:aRadix.
    s size < sz ifTrue:[
	s := ((String new:(sz - s size)) atAllPut:fillCharacter) , s
    ].
    ^ s

    "
     1024 printStringRadix:16 size:4 fill:$0
     1024 printStringRadix:2 size:16 fill:$.
     1024 printStringRadix:16 size:8 fill:(Character space)
    "
!

printHex
    "print the receiver as a hex number on the standard output stream"

     (self printStringRadix:16) print
!

errorPrintHex
    "print the receiver as a hex number on the standard error stream"

     (self printStringRadix:16) errorPrint
! !

!Integer class methodsFor:'instance creation'!

readFrom:aStream radix:radix
    "return the next unsigned Integer from the (character-)stream aStream 
     in radix; (assumes that the initial XXr has already been read).
     No whitespace-skipping is done.
     Returns 0 if no number available.

     NOTICE:   
       This behaves different from the default readFrom:, in returning
       0 (instead of raising an error) in case no number can be read.
       It is unclear, if this is the correct behavior (ST-80 does this)
       - depending on the upcoming ANSI standard, this may change."

    ^ self readFrom:aStream radix:radix onError:0
!

readFrom:aStream radix:radix onError:exceptionBlock
    "return the next unsigned Integer from the (character-)stream aStream 
     in radix; (assumes that the initial XXr has already been read).
     No whitespace-skipping is done.
     Returns the value of exceptionBlock, if no number is available."

    |nextChar value|

    nextChar := aStream peek.
    (nextChar notNil and:[nextChar isDigitRadix:radix]) ifFalse:[
	^ exceptionBlock value
    ].

    value := nextChar digitValue.
    nextChar := aStream nextPeek.
    [nextChar notNil and:[nextChar isDigitRadix:radix]] whileTrue:[
	value := value * radix + nextChar digitValue.
	nextChar := aStream nextPeek
    ].
    ^ value

    "
     Integer readFrom:(ReadStream on:'12345') radix:10  
     Integer readFrom:(ReadStream on:'FFFF') radix:16  
     Integer readFrom:(ReadStream on:'1010') radix:2   
     Integer readFrom:(ReadStream on:'foobar') radix:10   
     Integer readFrom:(ReadStream on:'foobar') radix:10 onError:nil  
    "
!

readFrom:aStream 
    "return the next unsigned Integer from the (character-)stream aStream 
     as decimal number. 

     NOTICE:   
       This behaves different from the default readFrom:, in returning
       0 (instead of raising an error) in case no number can be read.
       It is unclear, if this is the correct behavior (ST-80 does this)
       - depending on the upcoming ANSI standard, this may change."

    ^ self readFrom:aStream onError:0

    "
     Integer readFrom:(ReadStream on:'foobar')     
     Integer readFrom:(ReadStream on:'foobar') onError:nil  
    "
!

readFrom:aStringOrStream onError:exceptionBlock
    "return the next Integer from the (character-)stream aStream,
     handling initial XXr for arbitrary radix numbers and initial sign.
     Also, all initial whitespace is skipped.
     If the string does not represent a valid integer number,
     return the value of exceptionBlock."

    |str nextChar value negative|

    aStringOrStream isString ifTrue:[
	str := aStringOrStream readStream.
    ] ifFalse:[
	str := aStringOrStream
    ].

    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:[
	    'invalid (negative) radix ignored' errorPrintNL.
	    negative := false
	].
	str next.
	value := self readFrom:str radix:value onError:[^ exceptionBlock value]
    ].
    negative ifTrue:[
	^ value negated
    ].
    ^ value

    "
     Integer readFrom:'12345'   
     Integer readFrom:'-12345'   
     Integer readFrom:'+12345'   
     Integer readFrom:'16rFFFF'  
     Integer readFrom:'12345.1234' 
     Integer readFrom:'foo'
     Integer readFrom:'foo' onError:[0]
    "
! !