Integer.st
author Claus Gittinger <cg@exept.de>
Tue, 29 Dec 1998 17:56:57 +0100
changeset 3950 f9c4485a91d1
parent 3908 b893f399f517
child 3993 a5a09b2d36cd
permissions -rw-r--r--
avoid nil package return

"
 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 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.
"
!

documentation
"
    abstract superclass for all integer numbers.
    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

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


    [author:]
	Claus Gittinger

    [see also:]
	Number
	LargeInteger SmallInteger
	Float ShortFloat Fraction FixedPoint
"
! !

!Integer class methodsFor:'instance creation'!

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"

    |t|

    t := b4.
    t := (t bitShift:8) + b3.
    t := (t bitShift:8) + b2.
    ^ (t bitShift:8) + b1.

    "
     (Integer byte1:16r10 byte2:16r32 byte3:16r54 byte4:16r76) hexPrintString
     (Integer byte1:16r00 byte2:16r11 byte3:16r22 byte4:16r33) hexPrintString
    "

    "Created: 19.10.1997 / 18:08:52 / cg"
    "Modified: 19.10.1997 / 18:09:04 / cg"
!

fastFromString:aString at:startIndex
    "return the next unsigned Integer from the string 
     as a decimal number, starting at startIndex. 
     No spaces are skipped.

     This is a specially tuned entry (using a low-level C-call), which
     returns garbage if the argument string is not a small integer number.
     It has been added to allow higher speed string decomposition into
     numbers."
%{
     if (__isString(aString) && __isSmallInteger(startIndex)) {
        char *cp = (char *)(__stringVal(aString));
        int idx = __intVal(startIndex) - 1;
        INT val;

        if ((unsigned)idx < __stringSize(aString)) {
            val = atoi(cp + idx);
            RETURN (__MKINT(val));
        }
     }
%}.
     self primitiveFailed.

    "
     Integer fastFromString:'12345' at:1  
     Integer fastFromString:'12345' at:2  
     Integer fastFromString:'12345' at:3  
     Integer fastFromString:'12345' at:4  
     Integer fastFromString:'12345' at:5  
     Integer fastFromString:'12345' at:6  
     Integer fastFromString:'12345' at:0  

     Time millisecondsToRun:[
        100000 timesRepeat:[
            Integer readFrom:'12345'
        ]
     ]
    "

    "
     Time millisecondsToRun:[
        100000 timesRepeat:[
            Integer fastFromString:'12345' at:1  
        ]
     ]
    "
!

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])
!

readFrom:aStringOrStream 
    "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:aStringOrStream 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."

    ErrorSignal handle:[:ex |
        ^ exceptionBlock value
    ] do:[
        |str nextChar value negative|

        str := aStringOrStream readStream.

        nextChar := str skipSeparators.
        (nextChar == $-) ifTrue:[
            negative := true.
            str next.
            nextChar := str peekOrNil
        ] 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 peekOrNil.
        ((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
    ].

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

    "Created: / 16.11.1995 / 22:48:59 / cg"
    "Modified: / 14.4.1998 / 19:17:28 / cg"
!

readFrom:aStringOrStream 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:aStringOrStream radix:radix onError:0
!

readFrom:aStringOrStream 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."

    |str nextChar value|

    str := aStringOrStream readStream.

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

    value := nextChar digitValue.
    str next.
    nextChar := str peekOrNil.
    [nextChar notNil and:[nextChar isDigitRadix:radix]] whileTrue:[
        value := value * radix + nextChar digitValue.
        str next.
        nextChar := str peekOrNil.
    ].
    ^ 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  
    "

    "Modified: / 14.4.1998 / 19:16:46 / cg"
! !

!Integer class methodsFor:'constants'!

unity
    "return the neutral element for multiplication (1)"

    ^ 1

    "Modified: 18.7.1996 / 12:26:43 / cg"
!

zero
    "return the neutral element for addition (0)"

    ^ 0

    "Modified: 18.7.1996 / 12:26:38 / cg"
! !

!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:'VisualAge compatibility'!

<< aNumber
    "left shift"

    ^ self bitShift:aNumber

    "
     1 << 5 
     64 << -5 
    "
!

>> aNumber
    "right shift"

    ^ self bitShift:(aNumber negated)

    "
     1 >> -5  
     64 >> 5  
    "
!

isBitSet:index
    "return true if the index' bit is set; false otherwise.
     Bits are counted from 1 starting with the least significant."

    ^ (self bitAt:index) ~~ 0

    "
     5 isBitSet:3       => true
     2r0101 isBitSet:2  => false
     2r0101 isBitSet:1  => true
     2r0101 isBitSet:0  index error
    "
!

setBit:index
    "return a new number where the specified bit is on.
     Bits are counted from 1 starting with the least significant."

    ^ self bitOr:(1 bitShift:index-1)

    "
     0 setBit:3         => 4 (2r100)
     0 setBit:48        => 140737488355328 (2r1000.....000)
     ((0 setBit:99) setBit:100) printStringRadix:2  
    "
! !

!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."

    |n "{ Class: SmallInteger }"
     result 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 <= SmallInteger maxBytes]) ifTrue:[
	^ result compressed
    ].
    ^ result

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

    "Modified: 5.11.1996 / 14:06:26 / cg"
!

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 
     1 bitAt:2                     => 0
     1 bitAt:0                     index error
     2r1000100010001000100010001000100010001000100010001000 bitAt:48 => 1  
     2r1000100010001000100010001000100010001000100010001000 bitAt:47 => 0  

     (1 bitShift:1000) bitAt:1000  => 0
     (1 bitShift:1000) bitAt:1001  => 1
     (1 bitShift:1000) bitAt:1002  => 0

     (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     
    "
!

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

    |n "{ Class: SmallInteger }"
     result byte|

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

    1 to:n do:[:index |
        byte :=  (self digitAt:index) bitClear:(anInteger digitAt:index).
        result digitAt:index put:byte.
    ].
    (byte == 0 or:[n <= SmallInteger maxBytes]) ifTrue:[
        ^ result compressed
    ].
    ^ result
!

bitInvert
    "return a new integer, where all bits are complemented.
     This does not really make sense for negative largeIntegers,
     since the digits are stored as absolute value."

    |n "{ Class: SmallInteger }"
     result byte|

    n := self digitLength.
    result := self class basicNew numberOfDigits:n.

    1 to:n do:[:index |
        byte := self digitAt:index.
        result digitAt:index put:(byte bitInvert bitAnd:16rFF).
    ].
    (byte == 255 or:[n <= SmallInteger maxBytes]) ifTrue:[
        ^ result compressed
    ].
    ^ result
!

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

    |n "{ Class: SmallInteger }"
     result 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
!

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 }"
     nDigits    "{ Class: SmallInteger }" |

    shiftCount > 0 ifTrue:[
        "left shift"

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

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

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

    shiftCount < 0 ifTrue:[
        "right shift"

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

        digitShift >= n ifTrue:[
            ^ 0
        ].

        "
         modulo 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 to:n with:self digits startingAt:(digitShift + 1) .
            n <= SmallInteger maxBytes 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.

        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"

    "Modified: / 18.12.1997 / 17:17:29 / stefan"
    "Modified: / 8.7.1998 / 12:45:24 / cg"
!

bitTest:anInteger
    "return true, if the bitwise-and of the receiver and the argument, anInteger
     is non-0, false otherwise.
     This is a general and slow implementation, walking over the bytes of
     the receiver and the argument."

    |n "{ Class: SmallInteger }"
     result 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).
	byte ~~ 0 ifTrue:[^ true].
    ].
    ^ false

    "
     16r112233445566778899 bitTest:16rFF  
     16r112233445566778800 bitTest:16rFF  
     16r112233445566778899 bitTest:16rFFFFFFFFFFFFFFFF00  
     16r112233445566778899 bitTest:16rFF0000000000000000  
     16r112233445566778899 bitTest:16r00000000000000FFFF  
     16r1234567800000000 bitTest:16r8000000000000000  
     16r8765432100000000 bitTest:16r8000000000000000  
     16r12345678 bitTest:16r80000000  
     16r87654321 bitTest:16r80000000  
    "

    "Modified: 16.5.1996 / 16:29:50 / cg"
!

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

    |n "{ Class: SmallInteger }"
     result 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 compressed
    ].
    ^ result

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

    "Modified: 5.11.1996 / 14:06:40 / cg"
!

clearBit:index
    "return a new number where the specified bit is off.
     Bits are counted from 1 starting with the least significant."

    |n         "{ Class: SmallInteger }"
     byteIndex "{ Class: SmallInteger }"
     bitIndex "{ Class: SmallInteger }"
     result byte|

    byteIndex := ((index - 1) // 8) + 1.
    n := self digitLength.
    byteIndex > n ifTrue:[
        ^ self
    ].

    result := self copy.
    bitIndex := ((index - 1) \\ 8) + 1.
    byte := (result digitAt:byteIndex) clearBit:bitIndex.
    result digitAt:byteIndex put:byte.
    (byte == 0 or:[n == byteIndex and:[n <= SmallInteger maxBytes]]) ifTrue:[
        ^ result compressed
    ].
    ^ result

    "
     3111111111 clearBit:1 
    "

    "Modified: / 28.7.1998 / 18:35:50 / cg"
!

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  
    "
!

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

    |maxBytes "{ Class: SmallInteger }"
     bitIndex "{ Class: SmallInteger }" 
     byte|

    maxBytes := self digitLength.
    bitIndex := 0.
    1 to:maxBytes do:[:byteIndex |
	byte := self digitAt:byteIndex.
	byte ~~ 0 ifTrue:[
	    ^ bitIndex + byte lowBit
	].
	bitIndex := bitIndex + 8
    ].
    ^ -1

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

    "Modified: 1.3.1997 / 16:54:23 / cg"
! !

!Integer methodsFor:'byte access'!

digitByteLength
    "return the number bytes required for a 2's complement
     binary representation of this Integer.
     For positive receivers, thats the same as the digitLength."

    "
     check if there is a 0-byte ...
     this allows to ask unnormalized LargeIntegers 
     for their digitLength
    "
    |l "{ Class: SmallInteger }" |

    self >= 0 ifTrue:[^ self digitLength].

    l := self negated digitLength.
    (self digitByteAt:l) == 16rFF ifTrue:[
        ^ (l - 1) max:1
    ].
    ^ l

    "
     -129 digitByteLength 
    "

    "Created: / 25.10.1998 / 14:58:09 / cg"
    "Modified: / 25.10.1998 / 19:20:33 / cg"
! !

!Integer methodsFor:'coercing and converting'!

asFixedPoint
    "return the receiver as a fixedPoint number"

    ^ FixedPoint numerator:self denominator:1 scale:1

    "
     100 asFixedPoint      
     100 asFixedPoint + 0.1 asFixedPoint    
    "

    "Modified: 5.11.1996 / 15:13:17 / cg"
!

asFixedPoint:scale
    "return the receiver as fixedPoint number, with the given number
     of post-decimal-point digits."

    ^ FixedPoint numerator:self denominator:1 scale:scale

    "
     100 asFixedPoint:2      
     100 asFixedPoint + (0.1 asFixedPoint:2)    
    "

    "Modified: 10.1.1997 / 20:00:08 / cg"
!

asFraction
    "return a Fraction with same value as receiver"

    ^ Fraction basicNew setNumerator:self denominator:1

    "Modified: 28.7.1997 / 19:26:06 / cg"
!

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

    ^ self
!

signExtendedByteValue
    "return a smallInteger from sign-extending the 8'th bit.
     May be useful for communication interfaces"

    ^ (self bitAnd:16rFF) signExtendedByteValue

    "Created: 7.5.1996 / 09:31:52 / cg"
!

signExtendedShortValue
    "return a smallInteger from sign-extending the 16'th bit.
     May be useful for communication interfaces"

    ^ (self bitAnd:16rFFFF) signExtendedShortValue

    "Modified: 7.5.1996 / 09:31:57 / cg"
! !

!Integer methodsFor:'comparing'!

hash
    "redefined to return smallInteger hashValues"

    ^ self bitAnd:16r3FFFFFFF.

    "
        -20000000000000 hash 
         20000000000000 hash
    "

    "Created: / 14.11.1996 / 12:12:27 / cg"
    "Modified: / 24.2.1998 / 10:07:29 / stefan"
! !

!Integer methodsFor:'double dispatching'!

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)

    "Modified: 28.7.1997 / 19:08:30 / cg"
!

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

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

    "Modified: 28.7.1997 / 19:08:27 / cg"
!

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

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

    "Modified: 28.7.1997 / 19:08:23 / cg"
!

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

    "Modified: 28.7.1997 / 19:08:11 / cg"
! !

!Integer methodsFor:'helpers'!

gcd_helper:anInteger 
    "a helper for the greatest common divisor of the receiver and anInteger.
     Knuth's algorithm for large positive integers, with receiver being
     larger than the arg."

    | selfAbs argAbs selfLowBit argLowBit shift t |

    selfAbs := self.
    argAbs := anInteger.

    selfLowBit := selfAbs lowBit - 1.
    argLowBit := argAbs lowBit - 1.
    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.
    ].
    ^ argAbs bitShift:shift

    "Created: 1.3.1997 / 16:38:17 / cg"
    "Modified: 1.3.1997 / 16:45:17 / cg"
! !

!Integer methodsFor:'misc math'!

acker:n
    "return the value of acker(self, n).
      ;-) Do not try with receivers > 3"

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

    "
     3 acker:2  
    "

    "Modified: 18.7.1996 / 13:08:16 / cg"
!

divMod:aNumber
    "return an array filled with self // aNumber and
     self \\ aNumber. 
     The result is only defined for positive receiver and argument.
     This may be redefined in some integer classes for
     more performance (where the remainder is generated as a side effect of division)"

    ^ Array
	with:(self // aNumber)
	with:(self \\ aNumber)

    "  
     10 divMod:3  
     100 factorial divMod:103
    "

    "Modified: 29.10.1996 / 21:18:58 / cg"
!

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:[
	self < 0 ifTrue:[
	    "/
	    "/ requested factorial of a negative number
	    "/
            ^ self class
                raise:#domainErrorSignal
                receiver:self
                selector:#factorial
                errorString:'factorial of negative number'
	].
	^ 1
    ].
    p := 2.
    i := 3.
    [i <= self] whileTrue:[
	p := p * i.
	i := i + 1.
    ].
    ^ p

    "  
     10 factorial
     1000 factorial
     10000 factorial
     10000 factorialR

     Time millisecondsToRun:[2000 factorial] 
     Time millisecondsToRun:[2000 factorialR] 
     -1 factorial
    "

    "Modified: 29.10.1996 / 20:58:43 / cg"
!

factorialR
    "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
     faster and does not suffer from stack overflow problems (with big receivers)."

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

    "
     10 factorialR
     1000 factorialR
    "

    "Created: / 18.7.1996 / 12:48:36 / cg"
    "Modified: / 30.10.1998 / 22:10:33 / cg"
!

fib
    "compute the fibionacci number for the receiver.
     (same result as returned by #recursiveFib.
      This method shows how a changed algorithm can
      change things much more drastic than tuning ...
      ... compare 30 recursiveFib with 30 fib;
      and dont even try 60 recursiveFib)"

    |a1 a2 an|

    a1 := 1.
    a2 := 0.
    an := 0.
    self timesRepeat:[
	an := a1 + a2.
	a2 := a1.
	a1 := an
    ].
    ^ an

    "
     Transcript showCR:(Time millisecondsToRun:[30 fib]) 
     Transcript showCR:(Time millisecondsToRun:[30 recursiveFib]) 
     Transcript showCR:(Time millisecondsToRun:[60 fib])
     Transcript showCR:(Time millisecondsToRun:[200 fib])
     Transcript showCR:(Time millisecondsToRun:[1500 fib])
    "
!

gcd:anInteger 
    "return the greatest common divisor of the receiver and anInteger.
     Euclids & Knuths algorithm."

    |selfAbs argAbs t|

    selfAbs := self abs.
    argAbs := anInteger abs.

    selfAbs < argAbs ifTrue:[
	t := selfAbs.
	selfAbs := argAbs.
	argAbs := t.
    ].

    argAbs = 0 ifTrue: [^ selfAbs].
    selfAbs := selfAbs \\ argAbs.
    selfAbs = 0 ifTrue:[^ argAbs].
    ^ argAbs gcd_helper:selfAbs

    "                     
     3141589999999999 gcd:1000000000000000
    "

    "Modified: / 25.10.1997 / 16:08:45 / cg"
!

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

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

    "
     65 lcm:15
     3 lcm:15
    "
!

recursiveFib
    "compute the fibionacci number for the receiver.
     WARNING:
         Dont use this method if you need fibionacci numbers -
         this method is for benchmarking purposes only.
         (use #fib instead and dont ever try 60 recursiveFib ...)"

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

    "
     30 fib
     30 recursiveFib
     Transcript showCR:(Time millisecondsToRun:[30 recursiveFib])
     Transcript showCR:(Time millisecondsToRun:[30 fib])
    "

    "Modified: 18.7.1996 / 12:47:19 / cg"
! !

!Integer methodsFor:'printing & storing'!

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
    "
!

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

     (self printStringRadix:16) errorPrint
!

hexPrintString
    "return a hex string representation of the receiver"

    ^ self printStringRadix:16

    "
     127 hexPrintString
     -1 hexPrintString
    "

    "Modified: / 11.10.1998 / 01:15:43 / cg"
!

hexPrintString:size
    "return a hex string representation of the receiver,
     padded to size characters"

    ^ (self printStringRadix:16) leftPaddedTo:size with:$0

    "Created: 18.2.1997 / 13:32:33 / cg"
!

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

     (self printStringRadix:16) print
!

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

    self printOn:aStream base:10

    "Modified: / 20.1.1998 / 14:10:45 / stefan"
!

printOn:aStream base:base
    "return a string representation of the receiver in the specified
     radix (without the initial XXr)"

    |num s divMod mod r r2 r4 nD numN|

    (base between:2 and:36) ifFalse:[
        self error:'invalid base'.
        ^ self printOn:aStream base:10
    ].

    (self = 0) ifTrue:[aStream nextPut:$0. ^ self].
    (self < 0) ifTrue:[
        aStream nextPut:$- . 
        num := self negated.
    ] ifFalse:[
        num := self.
    ].

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

    "/ instead of computing the quotient and remainder
    "/ against radix, do it in junks of 5 or 6 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.

    r2 := base*base.   "/ radix^2
    r4 := r2*r2.             "/ radix^4
    base <= 10 ifTrue:[
        r := r4*r2.        "/ radix^6
        nD := 6.
    ] ifFalse:[
        r := r4*base.    "/ radix^5
        nD := 5.
    ].

    "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)
    "
    s := WriteStream on:(String new:((num highBit // base highBit - 1) + 1)).

    [num >= r] whileTrue:[
        "/
        "/ chop off nD digits.
        "/
        divMod := num divMod:r.
        num := divMod at:1.
        numN := divMod at:2.

        "/ process them
        nD timesRepeat:[
            divMod := numN divMod:base.
            numN := divMod at:1.
            mod := divMod at:2.
            s nextPut:(Character digitValue:mod).
        ].
    ].

    [num ~= 0] whileTrue:[
        divMod := num divMod:base.
        num := divMod at:1.
        mod := divMod at:2.
        s nextPut:(Character digitValue:mod).
    ].

    aStream nextPutAll:(s contents reverse).

    "
        3000 factorial printOn:Transcript base:10
        10 printOn:Transcript base:3
        31 printOn:Transcript base:3
        -20  printOn:Transcript base:16
        -20  printOn:Transcript base:10
    "

    "Modified: / 17.11.1997 / 16:27:45 / cg"
    "Modified: / 20.1.1998 / 18:05:02 / stefan"
!

printOn:aStream radix:base
    "append a printed description of the receiver to aStream.
     The receiver is printed in radix base (instead of the default, 10).
     This method is obsoleted by #printOn:base:, which is ST-80 compatible."

    self printOn:aStream base:base

    "Modified: / 20.5.1996 / 11:54:10 / cg"
    "Modified: / 20.1.1998 / 14:10:45 / stefan"
!

printStringRadix:base

    |s|

    s := WriteStream on:(String new:20).
    self printOn:s base:base.
    ^ s contents

    "Created: / 19.1.1998 / 17:20:58 / stefan"
    "Modified: / 20.1.1998 / 14:10:54 / stefan"
!

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 actualSize|

    s := self printStringRadix:aRadix.
    actualSize := s size.
    actualSize < sz ifTrue:[
	s := ((String new:(sz - actualSize)) 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)
    "
!

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

    |s|

    s := WriteStream on:(String new:20).
    base printOn:s.
    s nextPut:$r.
    self printOn:s base:base.
    ^ s contents

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

    "Created: / 19.1.1998 / 17:38:00 / stefan"
    "Modified: / 20.1.1998 / 14:11:03 / stefan"
! !

!Integer methodsFor:'queries'!

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     
    "
!

digitLength
    "return the number of bytes needed for the binary representation
     of the receiver.
     This method is redefined in concrete classes - the fallback here is
     never really used."

    ^ (self log:256) ceiling asInteger

    "Modified: 31.7.1997 / 13:19:06 / cg"
!

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

    ^ true
!

isPowerOfTwo
    "return true, if the receiver is a power of 2"

    ^ (self bitAnd:(self - 1)) == 0

    "
     0 isPowerOfTwo     
     1 isPowerOfTwo     
     2 isPowerOfTwo     
     3 isPowerOfTwo     
     4 isPowerOfTwo     
     16r8000000000000000 isPowerOfTwo
     16r8000000000000001 isPowerOfTwo
    "

    "Modified: 15.10.1997 / 18:43:49 / cg"
! !

!Integer methodsFor:'special bit operators'!

bitAnd_32:anInteger
    "return a C-semantic 32bit locical-and of the receiver and
     the argument. Both must be either Small- or LargeIntegers.
     This (nonstandard) specialized method is provided to allow simulation of
     and operations with C semantics."

%{  /* NOCONTEXT */
    int val1, val2, rslt;

    if (__isSmallInteger(self)) {
	val1 = __intVal(self);
    } else if (__isLargeInteger(self)) {
	val1 = __longIntVal(self);
	if (!val1) goto bad;
    } else {
	goto bad;
    }
    if (__isSmallInteger(anInteger)) {
	val2 = __intVal(anInteger);
    } else if (__isLargeInteger(anInteger)) {
	val2 = __longIntVal(anInteger);
	if (!val2) goto bad;
    } else {
	goto bad;
    }
    rslt = val1 & val2;
    RETURN(__MKINT(rslt));

  bad: ;
%}.
    self primitiveFailed.
!

bitOr_32:anInteger
    "return a C-semantic 32bit locical-or of the receiver and
     the argument. Both must be either Small- or LargeIntegers.
     This (nonstandard) specialized method is provided to allow simulation of
     and operations with C semantics."

%{  /* NOCONTEXT */
    int val1, val2, rslt;

    if (__isSmallInteger(self)) {
	val1 = __intVal(self);
    } else if (__isLargeInteger(self)) {
	val1 = __longIntVal(self);
	if (!val1) goto bad;
    } else {
	goto bad;
    }
    if (__isSmallInteger(anInteger)) {
	val2 = __intVal(anInteger);
    } else if (__isLargeInteger(anInteger)) {
	val2 = __longIntVal(anInteger);
	if (!val2) goto bad;
    } else {
	goto bad;
    }
    rslt = val1 | val2;
    RETURN(__MKINT(rslt));

  bad: ;
%}.
    self primitiveFailed.
! !

!Integer methodsFor:'truncation & rounding'!

ceiling
    "return the smallest integer which is larger or equal to the receiver.
     For integers, this is the receiver itself."

    ^ self

    "Modified: 18.7.1996 / 12:44:06 / cg"
!

compressed
    "if the receiver can be represented as a SmallInteger, return
     a SmallInteger with my value; otherwise return self with leading
     zeros removed. This method is redefined in LargeInteger."

    ^ self

    "Modified: 5.11.1996 / 14:07:41 / cg"
!

floor
    "return the largest integer which is smaller or equal to the receiver.
     For integers, this is the receiver itself."

    ^ self

    "Modified: 18.7.1996 / 12:44:00 / cg"
!

fractionPart
    "return a number with value from digits after the decimal point.
     (i.e. the receiver minus its truncated value)
     Since integers have no fraction, return 0 here."

    ^ 0

    "
     1234.56789 fractionPart      
     1.2345e6 fractionPart        
     1000 fractionPart              
     10000000000000000 fractionPart 
    "

    "Modified: 4.11.1996 / 20:27:44 / cg"
!

integerPart
    "return a number with value from digits before the decimal point.
     (i.e. the receivers truncated value)
     Since integers have no fraction, return the receiver here."

    ^ self

    "
     1234.56789 integerPart      
     1.2345e6 integerPart        
     1000 integerPart              
     10000000000000000 integerPart 
    "

    "Modified: 4.11.1996 / 20:28:22 / cg"
!

normalize
    "if the receiver can be represented as a SmallInteger, return
     a SmallInteger with my value; otherwise return self with leading
     zeros removed.
     This method is left for backward compatibility - it has been
     renamed to #compressed for ST-80 compatibility."

    ^ self compressed

    "Modified: 5.11.1996 / 14:08:24 / cg"
!

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

    ^ self

    "Modified: 18.7.1996 / 12:44:24 / cg"
!

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

    ^ self

    "Modified: 18.7.1996 / 12:44:33 / cg"
! !

!Integer class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.88 1998-10-30 21:10:56 cg Exp $'
! !