LargeInteger.st
author claus
Mon, 08 May 1995 05:31:14 +0200
changeset 339 e8658d38abfb
parent 250 a5deb61ffdac
child 345 cf2301210c47
permissions -rw-r--r--
.

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

Integer subclass:#LargeInteger
         instanceVariableNames:'sign digitByteArray'
         classVariableNames:''
         poolDictionaries:''
         category:'Magnitude-Numbers'
!

LargeInteger comment:'
COPYRIGHT (c) 1994 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libbasic/LargeInteger.st,v 1.14 1995-02-15 10:24:31 claus Exp $
'!

!LargeInteger class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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/LargeInteger.st,v 1.14 1995-02-15 10:24:31 claus Exp $
"
!

documentation
"
    This class provides arbitrary precision integers. These are represented as:
      sign (-1/0/+1) and, if sign ~~ 0
      a ByteArray of digits with 8 bits per element; 
      least significant 8 bits at index 1 ...

    The implementation is definitely not tuned for high performance
    (some key-methods should be rewritten as primitives),
    but ok for now, since LargeIntegers are not used very often.
    It will be reimplemented when everything else runs fine and a need arises
    (or someone rewrites it and sends me the code :-).

    For real speed, its implementation should be mapped onto a tuned arbitrary
    precision math package (maybe even special-cased for 32 and 64 bit 
    large-ints, since those are the most common).

    LargeIntegers are usually not created explicitely, but result from 
    SmallInteger arithmetic overflowing the SmallInteger range.
    Also, results of LargeInteger operations are converted to SmallIntegers,
    when possible (see normalize).

    In contrast to ST-80, there is only one class for LargeIntegers, keeping
    the sign as an instance variable (ST-80 has LargePositiveInteger and
    LargeNegativeInteger). This may change.
"
! !

!LargeInteger class methodsFor:'instance creation'!

value:aSmallInteger
    "create and return a new LargeInteger with value taken from
     the argument, aSmallInteger.
     Notice: this should be only used internally, since such small
     largeIntegers do not normally occur in the system.
     May change without notice."

    ^ self basicNew value:aSmallInteger

    "LargeInteger value:3689"
!

new:numberOfDigits
    "catch creation message"

    self error:'LargeIntegers cannot be created with new'
!

new
    "catch creation message"

    self error:'LargeIntegers cannot be created with new'
!

valueLow:lowBits hi:hiBits
    "create and return a new LargeInteger with value taken from
     the two 16-bit args, where the sign of the high bits determines
     the sign of the result. 
     The largeinteger is normalized (but not to a smallInteger).
     This method is called from the runtime system (+, -),
     when an integer result has to be converted to a Large.
     May change without notice."

    |newLarge|

    hiBits < 0 ifTrue:[
        newLarge := self unsignedValueLow:lowBits hi:(hiBits negated).
        newLarge sign:-1.
        ^ newLarge
    ].
    ^ self unsignedValueLow:lowBits hi:hiBits
!

unsignedValueLow:lowBits hi:hiBits
    "create and return a new LargeInteger with value taken from
     the two 16-bit unsigned args. 
     The largeinteger is normalized (but not to a smallInteger).
     This method is called from the runtime system (+, -),
     when an integer result has to be converted to a Large.
     May change without notice."

    |bytes b1 b2 b3 b4|

    b4 := (hiBits bitShift:-8) bitAnd:16rFF.
    b3 := hiBits bitAnd:16rFF.
    b2 := (lowBits bitShift:-8) bitAnd:16rFF.
    b1 := lowBits bitAnd:16rFF.

    b4 ~~ 0 ifTrue:[
        bytes := ByteArray with:b1 with:b2 with:b3 with:b4
    ] ifFalse:[
        b3 ~~ 0 ifTrue:[
            bytes := ByteArray with:b1 with:b2 with:b3
        ] ifFalse:[
            b2 ~~ 0 ifTrue:[
                bytes := ByteArray with:b1 with:b2
            ] ifFalse:[
                bytes := ByteArray with:b1
            ]
        ]
    ].
    ^ (self basicNew) setDigits:bytes
!

sign:s value16:ll value16:ml value16:mh value16:hh
    "create and return a new LargeInteger, with value taken from the
     four 16-bit unsigned value-args.
     This is sent internally, when a 64bit result has been created in
     SmallInteger multiplication or bitShift:.
     May change without notice."

    |newLarge digitBytes 
     hhI "{ Class: SmallInteger }"
     mhI "{ Class: SmallInteger }"
     mlI "{ Class: SmallInteger }"
     llI "{ Class: SmallInteger }"
     b1 "{ Class: SmallInteger }"
     b2 "{ Class: SmallInteger }"
     b3 "{ Class: SmallInteger }"
     b4 "{ Class: SmallInteger }"
     b5 "{ Class: SmallInteger }"
     b6 "{ Class: SmallInteger }"
     b7 "{ Class: SmallInteger }"
     b8 "{ Class: SmallInteger }"
     n "{ Class: SmallInteger }"|

    "
     this will change, once arguments can have a type-constraint
    "
    hhI := hh.
    mhI := mh.
    mlI := ml.
    llI := ll.

    "
     the following code is somewhat ugly, but includes an unrolled
     normalization, and is thus relatively fast ....
    "
    b8 := (hh bitShift:-8) bitAnd:16rFF.
    b7 := hh bitAnd:16rFF.
    b6 := (mh bitShift:-8) bitAnd:16rFF.
    b5 := mh bitAnd:16rFF.
    b4 := (ml bitShift:-8) bitAnd:16rFF.
    b3 := ml bitAnd:16rFF.
    b2 := (ll bitShift:-8) bitAnd:16rFF.
    b1 := ll bitAnd:16rFF.

    b8 ~~ 0 ifTrue:[
        n := 8
    ] ifFalse:[
        b7 ~~ 0 ifTrue:[
            n := 7.
        ] ifFalse:[
            b6 ~~ 0 ifTrue:[
                n := 6.
            ] ifFalse:[
                b5 ~~ 0 ifTrue:[
                    n := 5
                ] ifFalse:[
                    b4 ~~ 0 ifTrue:[
                        n := 4
                    ] ifFalse:[
                        b3 ~~ 0 ifTrue:[
                            n := 3
                        ] ifFalse:[
                            b2 ~~ 0 ifTrue:[
                                n := 2
                            ] ifFalse:[
                                n := 1
                            ]
                        ]
                    ]
                ]
            ]
        ]
    ].
        
        
    digitBytes := ByteArray uninitializedNew:n.
    digitBytes at:1 put:b1.
    n > 1 ifTrue:[
        digitBytes at:2 put:b2.
        n > 2 ifTrue:[
            digitBytes at:3 put:b3.
            n > 3 ifTrue:[
                digitBytes at:4 put:b4.
                n > 4 ifTrue:[
                    digitBytes at:5 put:b5.
                    n > 5 ifTrue:[
                        digitBytes at:6 put:b6.
                        n > 6 ifTrue:[
                            digitBytes at:7 put:b7.
                            n > 7 ifTrue:[
                                digitBytes at:8 put:b8.
                            ]
                        ]
                    ]
                ]
            ]
        ]
    ].

    newLarge := self basicNew setDigits:digitBytes.
    s < 0 ifTrue:[newLarge sign:s].
    ^ newLarge
! !

!LargeInteger methodsFor:'arithmetic'!

+ aNumber
    "return the sum of the receiver and the argument, aNumber"

    |otherSign|

    (sign == 0) ifTrue:[^ aNumber].  "cannot happen if correctly normalized"

    "
     this is the common case, adding a SmallInteger.
     Use a special method for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
        ^ self sumFromInteger:aNumber
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (aNumber class == self class) ifFalse:[
        ^ self retry:#+ coercing:aNumber
    ].

    otherSign := aNumber sign.
    (sign > 0) ifTrue:[
        "I am positive"
        (otherSign > 0) ifTrue:[^ self absPlus:aNumber].
        (otherSign < 0) ifTrue:[^ self absMinus:aNumber].
        ^ self
    ].
    "I am negative"
    (otherSign > 0) ifTrue:[^ aNumber absMinus:self].
    (otherSign < 0) ifTrue:[^ (self absPlus:aNumber) sign:-1].
    ^ self
!

- aNumber
    "return the difference of the receiver and the argument, aNumber"

    |otherSign result|

    (sign == 0) ifTrue:[^ aNumber negated].     "cannot happen if correctly normalized"

    "
     this is the common case, subtracting a SmallInteger.
     Use a special method for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
        sign < 0 ifTrue:[
            aNumber > 0 ifTrue:[
                result := (self absFastPlus:aNumber) sign:-1
            ] ifFalse:[
                result := (self absFastMinus:aNumber) sign:-1
            ].
        ] ifFalse:[
            aNumber > 0 ifTrue:[
                result := self absFastMinus:aNumber
            ] ifFalse:[
                result := self absFastPlus:aNumber
            ]
        ].
        ^ result normalize.
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (aNumber class == self class) ifFalse:[
        ^ self retry:#- coercing:aNumber
    ].

    otherSign := aNumber sign.
    (sign > 0) ifTrue:[
        "I am positive"
        (otherSign > 0) ifTrue:[^ self absMinus:aNumber].
        (otherSign < 0) ifTrue:[^ self absPlus:aNumber].
        ^ self
    ].
    "I am negative"
    (otherSign > 0) ifTrue:[^ (self absPlus:aNumber) negated].
    (otherSign < 0) ifTrue:[^ (self absMinus:aNumber) negated].
    ^ self

    "
     12345678901234567890 - 0     
     12345678901234567890 - 1    
     12345678901234567890 - -1    
     -12345678901234567890 - 1     
     -12345678901234567890 - -1    

     12345678901234567890 - 12345678901234567880     
     12345678901234567890 - 12345000000000000000     
     12345678901234567890 - -87654321098765432110    
     -12345678901234567890 - 87654321098765432110    
     -12345678901234567890 - -12345678901234567880   
     -12345678901234567890 - -12345678901234567980   
    "
!

* aNumber
    "return the product of the receiver and the argument, aNumber"

    |otherSign|

    (sign == 0) ifTrue:[^ 0].  "cannot happen if correctly normalized"

    "
     this is the common case, multiplying with SmallInteger.
     Use a special method for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
        ^ self productFromInteger:aNumber
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (aNumber class == self class) ifFalse:[
        ^ self retry:#* coercing:aNumber
    ].

    otherSign := aNumber sign.
    (sign == otherSign) ifTrue:[^ self absMul:aNumber].
    (otherSign == 0) ifTrue:[^ 0].
    ^ (self absMul:aNumber) sign:-1
!

// aNumber
    "return the quotient of the receiver and the argument, aNumber"

    |otherSign|

    otherSign := aNumber sign.

    "
     this is the common case, dividing by a SmallInteger.
     Use a special method for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
        (aNumber abs between:1 and:16r003fffff) ifTrue:[
            sign < 0 ifTrue:[
                (sign == otherSign) ifTrue:[^ (self absFastDiv:aNumber negated) at:1].
                ^ ((self absFastDiv:aNumber) at:1) sign:-1
            ].
            (sign == otherSign) ifTrue:[^ (self absFastDiv:aNumber) at:1].
            ^ ((self absFastDiv:aNumber negated) at:1) sign:-1
        ]
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (aNumber class == self class) ifFalse:[
        ^ self retry:#// coercing:aNumber
    ].

    sign < 0 ifTrue:[
        (sign == otherSign) ifTrue:[^ (self absDiv:aNumber negated) at:1].
        ^ ((self absDiv:aNumber) at:1) sign:-1
    ].
    (sign == otherSign) ifTrue:[^ (self absDiv:aNumber) at:1].
    ^ ((self absDiv:aNumber negated) at:1) sign:-1
!

\\ aNumber
    "return the remainder of division of the receiver by the argument, aNumber"

    |otherSign|

    otherSign := aNumber sign.

    "
     this is the common case, dividing by a SmallInteger.
     Use a special method for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
        (aNumber abs between:1 and:16r003fffff) ifTrue:[
            sign < 0 ifTrue:[
                (sign == otherSign) ifTrue:[^ (self absFastDiv:aNumber negated) at:2].
                ^ ((self absFastDiv:aNumber) at:2) sign:-1
            ].
            (sign == otherSign) ifTrue:[^ (self absFastDiv:aNumber) at:2].
            ^ ((self absFastDiv:aNumber negated) at:2) sign:-1
        ]
    ].

    "
     if the argument is not a largeInteger, coerce
    "
    (aNumber class == self class) ifFalse:[
        ^ self retry:#\\ coercing:aNumber
    ].

    sign < 0 ifTrue:[
        (sign == otherSign) ifTrue:[^ (self absDiv:aNumber negated) at:2].
        ^ ((self absDiv:aNumber) at:2) sign:-1
    ].
    (sign == otherSign) ifTrue:[^ (self absDiv:aNumber) at:2].
    ^ ((self absDiv:aNumber negated) at:2) sign:-1
!

/ aNumber
    "return the quotient of the receivers and the argument, aNumber"

    aNumber isInteger ifTrue:[
        ^ (Fraction numerator:self
                  denominator:aNumber) reduced
    ].

    "this is a q&d hack - we loose lots of precision here ..."
    ^ (self asFloat / aNumber asFloat)
!

negated
    "return an integer with value negated from the receivers value."

    |newNumber|

    (sign == 0) ifTrue:[^ 0].

    "
     special case for SmallInteger minVal
    "
    sign == 1 ifTrue:[
      digitByteArray size == 4 ifTrue:[
        (digitByteArray at:1) == 0 ifTrue:[
          (digitByteArray at:2) == 0 ifTrue:[
            (digitByteArray at:3) == 0 ifTrue:[
              (digitByteArray at:4) == 16r40 ifTrue:[
                ^ SmallInteger minVal
              ].
            ]
          ]
        ]
      ]
    ].
    newNumber := self shallowCopy.
    newNumber sign:(sign negated).
    ^ newNumber
! !

!LargeInteger methodsFor:'double dispatching'!

sumFromInteger:anInteger
    "sent, when anInteger does not know how to add the receiver.
     Return the sum of the receiver and the argument, (which must be a SmallInteger)"

    |result|

    anInteger > 0 ifTrue:[
        sign < 0 ifTrue:[
            result := (self absFastMinus:anInteger) sign:-1
        ] ifFalse:[
            result := self absFastPlus:anInteger
        ]
    ] ifFalse:[
        anInteger == 0 ifTrue:[
            ^ self
        ].
        sign < 0 ifTrue:[
            result := (self absFastPlus:anInteger abs) sign:-1
        ]  ifFalse:[
            result := self absFastMinus:anInteger
        ]
    ].
    ^ result normalize

    "
     12345678901234567890          
     -12345678901234567890         
     12345678901234567890 sumFromInteger:0       
     -12345678901234567890 sumFromInteger:0       
     12345678901234567890 sumFromInteger:1       
     12345678901234567890 sumFromInteger:-1      
     -12345678901234567890 sumFromInteger:1     
     -12345678901234567890 sumFromInteger:-1    
    "
!

differenceFromInteger:anInteger
    "sent, when anInteger does not know how to subtract the receiver.
     Return the result of 'anInteger - self'. The argument must be a SmallInteger."

    |result|

    anInteger > 0 ifTrue:[
        sign > 0 ifTrue:[
            result := (self absFastMinus:anInteger) sign:-1
        ] ifFalse:[
            result := self absFastPlus:anInteger
        ]
    ] ifFalse:[
        anInteger == 0 ifTrue:[
            ^ self negated
        ].
        sign > 0 ifTrue:[
            result := (self absFastPlus:anInteger negated) sign:-1
        ] ifFalse:[
            result := (self absFastMinus:anInteger) sign:-1
        ]
    ].
    ^ result normalize

    "
     12345678901234567890          
     -12345678901234567890         
     12345678901234567890 differenceFromInteger:0       
     12345678901234567890 differenceFromInteger:1       
     12345678901234567890 differenceFromInteger:-1      
     -12345678901234567890 differenceFromInteger:1   
     -12345678901234567890 differenceFromInteger:-1   
    "
!

productFromInteger:anInteger
    "sent, when anInteger does not know how to multiply the receiver.
     Return the product of the receiver and the argument, aSmallInteger"

    |num result 
     resultDigitByteArray
     val     "{ Class: SmallInteger }"
     len     "{ Class: SmallInteger }"
     carry   "{ Class: SmallInteger }"
     prod    "{ Class: SmallInteger }" 
     ok|

    "multiplying by a small integer is done here"

    "trivial cases"
    anInteger == 0 ifTrue:[^ 0].
    anInteger == 1 ifTrue:[^ self].

    num := anInteger abs.
    (num > 16r3FFFFF) ifTrue:[
        "if num is too big (so that multiplying by a byte could create a Large)"

        ^ anInteger retry:#* coercing:self
    ].

    len := digitByteArray size.

    result := self class basicNew numberOfDigits:(len + 4).

    "used to be the following. replaced, to avoid another multiplication"
"
    result sign:(sign * anInteger sign).
"
    anInteger < 0 ifTrue:[
        sign > 0 ifTrue:[
            result sign:-1
        ].
    ] ifFalse:[
        sign < 0 ifTrue:[
            result sign:sign
        ]
    ].

    resultDigitByteArray := result digits.

    carry := 0.
    val := num.

    ok := false.
%{
    if (__bothSmallInteger(len, val)
     && __isByteArray(_INST(digitByteArray))
     && __isByteArray(resultDigitByteArray)) {
        int _l = _intVal(len);
        int _v = _intVal(val);
        unsigned _carry = 0;
        unsigned _prod;
        unsigned char *digitP = _ByteArrayInstPtr(_INST(digitByteArray))->ba_element;
        unsigned char *resultP = _ByteArrayInstPtr(resultDigitByteArray)->ba_element;

        while (_l-- > 0) {
            _prod = *digitP++ * _v + _carry;
            *resultP++ = _prod & 0xFF;
            _carry = _prod >> 8;
        }
        while (_carry) {
            *resultP++ = _carry & 0xFF;
            _carry >>= 8;
        }
        ok = true;
    }
%}.
    "
     fall back - normally not reached
     (could make it a primitive-failure as well)
    "
    ok ifFalse:[
        1 to:len do:[:i |
            prod := (digitByteArray basicAt:i) * val + carry.
            resultDigitByteArray basicAt:i put:(prod bitAnd:16rFF).
            carry := prod bitShift:-8.
        ].
        [carry ~~ 0] whileTrue:[
            len := len + 1.
            resultDigitByteArray basicAt:len put:(carry bitAnd:16rFF).
            carry := carry bitShift:-8
        ].
    ].
    ^ result normalize
! !

!LargeInteger methodsFor:'coercing & converting'!

coerce:aNumber
    "return the argument as a LargeInteger"

    ^ aNumber asLargeInteger
!

value:aSmallInteger
    "return a new LargeInteger with value taken from a SmallInteger.
     This method will fail, if the argument is not a smallInteger."

    |absValue 
     b1 "{ Class: SmallInteger }"
     b2 "{ Class: SmallInteger }"
     b3 "{ Class: SmallInteger }"|

    "
     could have simply created a 4-byte largeinteger and normalize
     it; the code below does the normalize right away, avoiding the
     overhead of producing any intermediate byte-arrays (and the scanning)
    "
    (aSmallInteger == 0) ifTrue: [
        digitByteArray := #[0].
        sign := 0.
        ^ self
    ].
    (aSmallInteger < 0) ifTrue: [
        sign := -1.
        absValue := aSmallInteger negated
    ] ifFalse: [
        sign := 1.
        absValue := aSmallInteger
    ].
    b1 := absValue bitAnd:16rFF.
    absValue := absValue bitShift:-8.
    absValue == 0 ifTrue:[
        digitByteArray := ByteArray with:b1
    ] ifFalse:[
        b2 := absValue bitAnd:16rFF.
        absValue := absValue bitShift:-8.
        absValue == 0 ifTrue:[
            digitByteArray := ByteArray with:b1 with:b2
        ] ifFalse:[
            b3 := absValue bitAnd:16rFF.
            absValue := absValue bitShift:-8.
            absValue == 0 ifTrue:[
                digitByteArray := ByteArray with:b1 with:b2 with:b3
            ] ifFalse:[
                digitByteArray := ByteArray with:b1 with:b2 with:b3 with:absValue
            ]
        ]
    ]
!

asSmallInteger
    "return a SmallInteger with same value as myself - 
     the result is invalid if the receivers value cannot 
     be represented as a SmallInteger.
     Q: should we raise an exception if this happens ?"

    |value|

    value := 0.
    (sign == 0) ifFalse:[
        digitByteArray reverseDo:[:aDigit |
            value := (value times:256) + aDigit 
        ].
        (sign < 0) ifTrue:[
            value := value negated
        ]
    ].
    ^ value
!

asLargeInteger
    "return a LargeInteger with same value as myself - thats me"

    ^ self
!

asFloat
    "return a Float with same value as myself.
     Since floats have a limited precision, you usually loose bits when
     doing this."

    |newFloat|

    newFloat := 0.0.
    (sign == 0) ifFalse:[
        digitByteArray reverseDo:[:aDigit |
            newFloat := (newFloat * 256.0) + aDigit asFloat
        ].
        (sign < 0) ifTrue:[
            newFloat := newFloat negated
        ]
    ].
    ^ newFloat

    "
     1234567890 asFloat               
     12345678901234567890 asFloat      
     12345678901234567890 asFloat asInteger   
    "
!

normalize
    "if the receiver can be represented as a SmallInteger, return
     a SmallInteger with my value; otherwise return self with leading
     zeros removed"

    |index "{ Class: SmallInteger }" 
     val   "{ Class: SmallInteger }" |

%{
    OBJ t;

    t = _INST(digitByteArray);
    if (__isByteArray(t)) {
        unsigned char *_digitBytes = _ByteArrayInstPtr(t)->ba_element;
        int _idx = _byteArraySize(t);
        int _val;

        if (_INST(sign) == _MKSMALLINT(0)) {
            RETURN (_MKSMALLINT(0));
        }

        while ((_idx > 0) && (_digitBytes[_idx - 1] == 0)) {
            _idx--;
        }
        switch (_idx) {
            case 0:
                RETURN (_MKSMALLINT(0));
                break;

            case 1:
                _val = _digitBytes[0];
                if (_INST(sign) == _MKSMALLINT(-1))
                    _val = -_val;
                RETURN (_MKSMALLINT(_val));
                
            case 2:
                _val = (_digitBytes[1]<<8) + _digitBytes[0];
                if (_INST(sign) == _MKSMALLINT(-1))
                    _val = -_val;
                RETURN (_MKSMALLINT(_val));

            case 3:
                _val = (((_digitBytes[2]<<8) + _digitBytes[1])<<8) + _digitBytes[0];
                if (_INST(sign) == _MKSMALLINT(-1))
                    _val = -_val;
                RETURN (_MKSMALLINT(_val));

            case 4:
                _val = _digitBytes[3];
                if (_val <= 0x40) {
                    _val = (((((_val<<8) + _digitBytes[2])<<8) + _digitBytes[1])<<8) + _digitBytes[0];
                    if (_INST(sign) == _MKSMALLINT(-1))
                        _val = -_val;
                    if ((_val >= _MIN_INT) && (_val <= _MAX_INT)) {
                        RETURN (_MKSMALLINT(_val));
                    }
                }
                break;

            default:
                break;
        }
        index = _MKSMALLINT(_idx);
    } else {
        index = _MKSMALLINT(0);
    }
%}.
    index == 0 ifTrue:[
        "
         fall back code - in case digitByteArray is not a byteArray
        "
        index := digitByteArray size.
        [(index > 0) and:[(digitByteArray at:index) == 0]] whileTrue:[
            index := index - 1
        ].
        (index == 1) ifTrue:[
            val := (digitByteArray at:1).
            sign < 0 ifTrue:[
                ^ val negated
            ].
            ^ val
        ].
        (index == 2) ifTrue:[
            val := digitByteArray at:2.
            val := (val bitShift:8) + (digitByteArray at:1).
            sign < 0 ifTrue:[
                ^ val negated
            ].
            ^ val
        ].
        (index == 3) ifTrue:[
            val := digitByteArray at:3.
            val := (val bitShift:8) + (digitByteArray at:2).
            val := (val bitShift:8) + (digitByteArray at:1).
            sign < 0 ifTrue:[
                ^ val negated
            ].
            ^ val
        ].
        index == 4 ifTrue:[
            val := digitByteArray at:4.
            val <= 16r3F ifTrue:[
                val := (val bitShift:8) + (digitByteArray at:3).
                val := (val bitShift:8) + (digitByteArray at:2).
                val := (val bitShift:8) + (digitByteArray at:1).
                sign < 0 ifTrue:[
                    ^ val negated
                ].
                ^ val
            ].
            val == 16r40 ifTrue:[
                sign < 0 ifTrue:[
                    ((digitByteArray at:3) == 0
                    and:[(digitByteArray at:2) == 0
                    and:[(digitByteArray at:1) == 0]]) ifTrue:[
                        ^ SmallInteger minVal
                    ]
                ]
            ]
        ].
        (index == 0) ifTrue:[
            ^ 0
        ].
    ].

    (index ~~ digitByteArray size) ifTrue:[
        digitByteArray := digitByteArray copyFrom:1 to:index
    ].
    ^ self
! !

!LargeInteger methodsFor:'byte access'!

digitLength
    "return the number bytes used by this Integer"

    ^ digitByteArray size
!

digitAt:index
    "return 8 bits of value, starting at byte index"

    index > digitByteArray size ifTrue:[^ 0].
    ^ digitByteArray at:index
!

digitAt:index put:aByte
    "set the 8 bits, index is a byte index"

    digitByteArray at:index put:aByte
!

digits
    "return a byteArray fille with the receivers bits
     (8 bits of the absolute value per element)"

    ^ digitByteArray
! !

!LargeInteger methodsFor:'private'!

sign:aNumber
    sign := aNumber
!

numberOfDigits:nDigits
    digitByteArray := ByteArray new:nDigits.
    sign := 1.
!

setDigits:digits
    digitByteArray := digits.
    sign := 1.
!

absFastPlus:aSmallInteger
    "return a LargeInteger representing abs(self) + abs(theArgument).
     The result is not normalized."

    |result resultDigitByteArray
     len   "{ Class: SmallInteger }"
     index "{ Class: SmallInteger }"
     carry "{ Class: SmallInteger }" |

    len := digitByteArray size.

    result := self class basicNew numberOfDigits:(len + 1).
    resultDigitByteArray := result digits.

    index := 1.
    carry := aSmallInteger abs.

    [carry ~~ 0] whileTrue:[
        (index <= len) ifTrue:[
            carry := (digitByteArray basicAt:index) + carry.
        ].
        resultDigitByteArray basicAt:index put:(carry bitAnd:16rFF).
        carry := carry bitShift:-8.
        index := index + 1
    ].
    [index <= len] whileTrue:[
        resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
        index := index + 1
    ].

    ^ result
!

absFastMinus:aSmallInteger
    "return a LargeInteger representing abs(self) - abs(theArgument).
     The result is not normalized."

    |result resultDigitByteArray
     len   "{ Class: SmallInteger }"
     index "{ Class: SmallInteger }"
     borrow "{ Class: SmallInteger }"
     diff  "{ Class: SmallInteger }" |

    len := digitByteArray size.

    result := self class basicNew numberOfDigits:(len + 1).
    resultDigitByteArray := result digits.

    index := 1.
    borrow := aSmallInteger abs.

    [borrow ~~ 0] whileTrue:[
        (index <= len) ifTrue:[
            diff := (digitByteArray basicAt:index) - (borrow bitAnd:16rFF).
            borrow := borrow bitShift:-8.
            diff < 0 ifTrue:[
                diff := diff + 256.
                borrow := borrow + 1.
            ]
        ] ifFalse:[
            diff := borrow bitAnd:255.
            borrow := borrow bitShift:-8.
        ].
        resultDigitByteArray basicAt:index put:diff.
        index := index + 1
    ].
    [index <= len] whileTrue:[
        resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
        index := index + 1
    ].

    ^ result

    "                                                          
     12345678900000000000 absFastMinus:1       
     12345678900000000000 absFastMinus:1000000  
     12345678900000000000 absFastMinus:255
     (SmallInteger maxVal + 1) absFastMinus:1  
     (SmallInteger minVal - 1) absFastMinus:1  
    "
!

absFastDiv:aSmallInteger
    "return an array with two LargeIntegers representing
     abs(self) // aSmallInteger and abs(self) \\ aSmallInteger"

    |tmp1     "{ Class: SmallInteger }"
     prevRest "{ Class: SmallInteger }"
     count    "{ Class: SmallInteger }"
     newDigitByteArray result
     ok|

    aSmallInteger == 0 ifTrue:[
        ^ DivisionByZeroSignal raise
    ].

"This cannot happen (if always normalized)
    self < aSmallInteger ifTrue:[
        ^ Array with:0 with:self
    ].
"
    count := digitByteArray size.
    result := self class basicNew numberOfDigits:count.
    newDigitByteArray := result digits.
    ok := false.
%{
    if (__isByteArray(_INST(digitByteArray))
     && __isByteArray(newDigitByteArray)
     && __bothSmallInteger(count, aSmallInteger)) {
        unsigned int rest = 0;
        int index = _intVal(count);
        int divisor = _intVal(aSmallInteger);
        unsigned char *digitBytes = _ByteArrayInstPtr(_INST(digitByteArray))->ba_element;
        unsigned char *resultBytes = _ByteArrayInstPtr(newDigitByteArray)->ba_element;

        while (index > 0) {
            unsigned int t;

            index--;
            t = digitBytes[index];
            t = t | (rest << 8);
            resultBytes[index] = t / divisor;
            rest = t % divisor;
        }
        prevRest = _MKSMALLINT(rest);
        ok = true;
    }
%}.
    "
     slow code - not normally reached
     (could also do a primitiveFailure here)
    "
    ok ifFalse:[
        prevRest := 0.
        count to:1 by:-1 do:[:i |
            tmp1 := digitByteArray at:i.
            tmp1 := (tmp1 + (prevRest * 256)).
            newDigitByteArray at:i put:tmp1 // aSmallInteger.
            prevRest := (tmp1 \\ aSmallInteger).
        ]
    ].

    ^ Array with:(result normalize) with:prevRest
!

absMul:aLargeInteger
    "return a LargeInteger representing abs(self) * abs(theArgument)"

    |result otherDigitByteArray resultDigitByteArray ok
     idx      "{ Class: SmallInteger }"
     carry    "{ Class: SmallInteger }"
     len1     "{ Class: SmallInteger }"
     len2     "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     prod     "{ Class: SmallInteger }"
     v        "{ Class: SmallInteger }"|

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digits.
    len2 := otherDigitByteArray size.

    result := LargeInteger basicNew numberOfDigits:(len1 + len2 + 1).
    resultDigitByteArray := result digits.
    ok := false.
%{
    if (__isByteArray(_INST(digitByteArray))
     && __isByteArray(otherDigitByteArray)
     && __isByteArray(resultDigitByteArray)
     && __bothSmallInteger(len1, len2)) {
        unsigned char *myBytes = _ByteArrayInstPtr(_INST(digitByteArray))->ba_element;
        unsigned char *otherBytes = _ByteArrayInstPtr(otherDigitByteArray)->ba_element;
        unsigned char *resultBytes = _ByteArrayInstPtr(resultDigitByteArray)->ba_element;
        int _index1, _index2, _dstIndex, _idx;
        unsigned _prod, _carry, _v;

        for (_index1 = 0; _index1 < _intVal(len1); _index1++) {
            for (_index2 = 0; _index2 < _intVal(len2); _index2++) {
                _dstIndex = _index1 + _index2;
                _prod = myBytes[_index1] * otherBytes[_index2];
                _prod += resultBytes[_dstIndex];
                resultBytes[_dstIndex] = _prod & 0xFF;
                _carry = _prod >> 8;
                if (_carry) {
                    _idx = _dstIndex + 1;
                    while (_carry) {
                        _v = resultBytes[_idx] + _carry;
                        resultBytes[_idx] = _v & 0xFF;
                        _carry = _v >> 8;
                        _idx = _idx + 1;
                    }
                }
            }
        }
        ok = true;
    }
%}.
    ok ifFalse:[
        1 to:len1 do:[:index1 |
            1 to:len2 do:[:index2 |
                dstIndex := index1 + index2 - 1.
                prod := (digitByteArray basicAt:index1) * (otherDigitByteArray basicAt:index2).
                prod := prod + (resultDigitByteArray basicAt:dstIndex).
                resultDigitByteArray basicAt:dstIndex put:(prod bitAnd:16rFF).
                carry := prod bitShift:-8.
                carry ~~ 0 ifTrue:[
                    idx := dstIndex + 1.
                    [carry ~~ 0] whileTrue:[
                        v := (resultDigitByteArray basicAt:idx) + carry.
                        resultDigitByteArray basicAt:idx put:(v bitAnd:255).
                        carry := v bitShift:-8.
                        idx := idx + 1
                    ]
                ]
            ]
        ].
    ].
    ^ result normalize
!

absLess:aLargeInteger
    "return true, if abs(self) < abs(theArgument)"

    |len1 "{ Class: SmallInteger }"
     len2 "{ Class: SmallInteger }"
     d1   "{ Class: SmallInteger }"
     d2   "{ Class: SmallInteger }"
     otherDigitByteArray |

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digits.
    len2 := otherDigitByteArray size.

    [(digitByteArray basicAt:len1) == 0] whileTrue:[
        len1 := len1 - 1
    ].
    [(otherDigitByteArray basicAt:len2) == 0] whileTrue:[
        len2 := len2 - 1
    ].
    (len1 < len2) ifTrue:[^ true].
    (len1 > len2) ifTrue:[^ false].

    [len1 > 0] whileTrue:[
        d1 := digitByteArray basicAt:len1.
        d2 := otherDigitByteArray basicAt:len1.
        (d1 < d2) ifTrue:[^ true].
        (d1 > d2) ifTrue:[^ false].
        len1 := len1 - 1
    ].
    ^ false
!

absEq:aLargeInteger
    "return true, if abs(self) = abs(theArgument)"

    |len1 "{ Class: SmallInteger }"
     len2 "{ Class: SmallInteger }"
     d1   "{ Class: SmallInteger }"
     d2   "{ Class: SmallInteger }"
     otherDigitByteArray |

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digits.
    len2 := otherDigitByteArray size.

    [(digitByteArray basicAt:len1) == 0] whileTrue:[
        len1 := len1 - 1
    ].
    [(otherDigitByteArray basicAt:len2) == 0] whileTrue:[
        len2 := len2 - 1
    ].
    (len1 ~~ len2) ifTrue:[^ false].
    [len1 > 0] whileTrue:[
        d1 := digitByteArray basicAt:len1.
        d2 := otherDigitByteArray basicAt:len1.
        (d1 ~~ d2) ifTrue:[^ false].
        len1 := len1 - 1
    ].
    ^ true
!

absPlus:aLargeInteger
    "return a LargeInteger representing abs(self) + abs(theArgument)"

    |result done otherDigitByteArray resultDigitByteArray
     len1  "{ Class: SmallInteger }"
     len2  "{ Class: SmallInteger }"
     index "{ Class: SmallInteger }"
     carry "{ Class: SmallInteger }"
     sum   "{ Class: SmallInteger }" |

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digits.
    len2 := otherDigitByteArray size.

    result := self class basicNew numberOfDigits:((len1 max: len2) + 1).
    resultDigitByteArray := result digits.

    index := 1.
    carry := 0.

    done := false.
    [done] whileFalse:[
        sum := carry.
        (index <= len1) ifTrue:[
            sum := sum + (digitByteArray basicAt:index).
            (index <= len2) ifTrue:[
                sum := sum + (otherDigitByteArray basicAt:index)
            ]
        ] ifFalse:[
            (index <= len2) ifTrue:[
                sum := sum + (otherDigitByteArray basicAt:index)
            ] ifFalse:[
                "end reached"
                done := true
            ]
        ].
        (sum >= 16r100) ifTrue:[
            carry := 1.
            sum := sum - 16r100
        ] ifFalse:[
            carry := 0
        ].
        resultDigitByteArray basicAt:index put:sum.
        index := index + 1
    ].
    ^ result normalize
!

absMinus:aLargeInteger
    "return a LargeInteger representing abs(self) - abs(theArgument)"

    |result done
     otherDigitByteArray resultDigitByteArray
     len1   "{ Class: SmallInteger }"
     len2   "{ Class: SmallInteger }"
     index  "{ Class: SmallInteger }"
     borrow "{ Class: SmallInteger }"
     diff   "{ Class: SmallInteger }"
     sum    "{ Class: SmallInteger }"
     carry  "{ Class: SmallInteger }" |

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digits.
    len2 := otherDigitByteArray size.

    result := self class basicNew numberOfDigits:((len1 max: len2) + 1).
    resultDigitByteArray := result digits.

    index := 1.
    borrow := 0.

    done := false.
    [done] whileFalse:[
        diff := borrow.
        (index <= len1) ifTrue:[
            diff := diff + (digitByteArray basicAt:index).
            (index <= len2) ifTrue:[
                diff := diff - (otherDigitByteArray basicAt:index)
            ]
        ] ifFalse:[
            (index <= len2) ifTrue:[
                diff := diff - (otherDigitByteArray basicAt:index)
            ] ifFalse:[
                "end reached"
                done := true
            ]
        ].
"/ workaround for
"/ gcc code generator bug
"/

(diff >= 0) ifTrue:[
    borrow := 0
] ifFalse:[
    borrow := -1.
    diff := diff + 16r100
].
"/        (diff < 0) ifTrue:[
"/            borrow := -1.
"/            diff := diff + 16r100
"/        ] ifFalse:[
"/            borrow := 0
"/        ].
        resultDigitByteArray basicAt:index put:diff.
        index := index + 1
    ].
    (borrow ~~ 0) ifTrue:[
        result sign: -1.
        carry := 0.
        1 to:(index - 1) do:[:i |
            sum := ((resultDigitByteArray at:i) + carry - 16r100) negated.
            resultDigitByteArray at:i put:sum.
            carry := 1
        ]
    ].
    ^ result normalize
!

absDiv:anInteger
    "return an array with two LargeIntegers representing
     abs(self) // abs(theArgument) and abs(self) \\ abs(theArgument).
     This needs a rewrite."

    |tmp1 tmp2 
     rem 
     count "{ Class: SmallInteger }"
     digit "{ Class: SmallInteger }" |

    anInteger == 0 ifTrue:[
        ^ DivisionByZeroSignal raise
    ].

    self < anInteger ifTrue:[
        ^ Array with:0 with:self
    ].

    tmp1 := self simpleDeepCopy.
    tmp2 := anInteger simpleDeepCopy.
    count := 0.
    [tmp2 < tmp1] whileTrue:[
        tmp2 mul256.
        count := count + 1
    ].

    tmp2 div256.

    rem := 0 asLargeInteger. 
    [count == 0] whileFalse:[
        digit := 0.
        [tmp1 >= tmp2] whileTrue:[
            digit := digit + 1.
            tmp1 := tmp1 - tmp2
        ].
        rem := rem * 256 + digit.
        tmp2 div256.
        count := count - 1
    ].
    ^ Array with:rem with:tmp1 
!

div256
    "destructively divide the receiver by 256.
     private - used for division only"

    digitByteArray replaceFrom:1 with:digitByteArray startingAt:2.
    digitByteArray at:(digitByteArray size) put:0
!

mul256
    "destructively multiply the receiver by 256.
     private - used for division only"

    |newDigits|

    newDigits := ByteArray new:(digitByteArray size + 1).
    newDigits replaceFrom:2 with:digitByteArray startingAt:1.
    newDigits at:1 put:0.
    digitByteArray := newDigits
! !

!LargeInteger methodsFor:'comparing'!

= aNumber
    "return true, if the argument, aNumber has the same value as
     the receiver"

    (aNumber class == self class) ifFalse:[
        aNumber respondsToArithmetic ifFalse:[ ^ false ].
        ^ self retry:#= coercing:aNumber
    ].
    (aNumber sign == sign) ifFalse:[^ false].
    ^ self absEq:aNumber
!

< aNumber
    "return true, if the argument, aNumber is greater than the receiver"

    |otherSign|

    (aNumber class == self class) ifFalse:[
        ^ self retry:#< coercing:aNumber
    ].
    otherSign := aNumber sign.

    (sign > 0) ifTrue:[
        "I am positive"
        (otherSign > 0) ifTrue:[^ self absLess:aNumber].
        ^ false "aNumber is <= 0"
    ].
    (sign == 0) ifTrue:[
        (otherSign > 0) ifTrue:[^ true].
        ^ false
    ].
    "I am negative"
    (otherSign > 0) ifTrue:[^ true].
    (otherSign == 0) ifTrue:[^ true].
    ^ (self absLess:aNumber) not
!

> aNumber
    "return true, if the argument, aNumber is less than the receiver"

    |otherSign|

    (aNumber class == self class) ifFalse:[
        ^ self retry:#> coercing:aNumber
    ].
    otherSign := aNumber sign.

    (sign > 0) ifTrue:[
        "I am positive"
        (otherSign > 0) ifTrue:[^ aNumber absLess:self].
        ^ true "aNumber is <= 0"
    ].
    (sign == 0) ifTrue:[
        "I am zero"
        (otherSign > 0) ifTrue:[^ false].
        ^ true
    ].
    "I am negative"
    (otherSign > 0) ifTrue:[^ false].
    (otherSign == 0) ifTrue:[^ false].
    ^ (self absLess:aNumber) not
! !

!LargeInteger methodsFor:'testing'!

sign
    "return the sign of the receiver"

    ^ sign
!

negative
    "return true, if the receiver is < 0"

    ^ (sign < 0)
!

odd
    "return true if the receiver is odd"

    ^ (digitByteArray at:1) even
!

even
    "return true if the receiver is even"

    ^ (digitByteArray at:1) even
!

positive
    "return true, if the receiver is >= 0"

    ^ (sign >= 0)
!

strictlyPositive
    "return true, if the receiver is > 0"

    ^ (sign > 0)
! !

!LargeInteger methodsFor:'printing & storing'!

storeOn:aStream
    "append a representation of the receiver to aStream, which can
     be used to reconstruct the receiver."

    self printOn:aStream.
    aStream nextPutAll:' asLargeInteger'
! !