LargeInt.st
author Claus Gittinger <cg@exept.de>
Tue, 07 Jan 1997 12:02:05 +0100
changeset 2072 e84dbf5e5424
parent 2001 8c2b957f0cb3
child 2267 123ec897aca5
permissions -rw-r--r--
removed package-change info message

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

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

    [author:]
	Claus Gittinger

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

!LargeInteger class methodsFor:'instance creation'!

new
    "catch creation message"

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

new:numberOfDigits
    "catch creation message"

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

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

!LargeInteger class methodsFor:'queries'!

isBuiltInClass
    "return true if this class is known by the run-time-system.
     Here, true is returned."

    ^ true

    "Modified: 23.4.1996 / 15:59:21 / cg"
! !

!LargeInteger methodsFor:'arithmetic'!

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

    "
     SmallInteger maxVal 
     SmallInteger maxVal + 1  
     SmallInteger maxVal + 2 
     SmallInteger minVal    
     SmallInteger minVal - 1
    "
!

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

    |otherSign|

    (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:[
		^ (self absFastPlus:aNumber) sign:-1
	    ].
	    ^ (self absFastMinus:aNumber) sign:-1
	].
	aNumber > 0 ifTrue:[
	    ^ self absFastMinus:aNumber
	].
	^ self absFastPlus: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 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   
    "

    "Modified: 20.10.1996 / 18:42:16 / cg"
!

/ aNumber
    "return the quotient of the receiver 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)
!

// aNumber
    "return the quotient of the receiver and the argument, aNumber.
     The result is truncated toward negative infinity and negative,
     if the operands signs differ."

    |otherSign divMod d quo abs "{ Class: SmallInteger }" n|

    otherSign := aNumber sign.

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

	    "/ stupid adjust ...
	    (divMod at:2) == 0 ifFalse:[
		^ (quo sign:-1) - 1
	    ].
	    ^ quo sign:-1
	].
	n := aNumber asLargeInteger.
    ] ifFalse:[
	n := aNumber
    ].

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

    divMod := self absDiv:n.

    (sign == otherSign) ifTrue:[^ divMod at:1].

    "/ stupid adjust for truncation ...
    quo := divMod at:1.
    (divMod at:2) == 0 ifFalse:[
	^ (quo sign:-1) - 1
    ].
    ^ quo sign:-1

    "
     900 // 400  
     -900 // 400 
     900 // -400  
     -900 // -400

     9000000000 // 4000000000
     -9000000000 // 4000000000 
     9000000000 // -4000000000 
     -9000000000 // -4000000000

     900 quo: 400   
     -900 quo: 400  
     900 quo: -400  
     -900 quo: -400 

     9000000000 quo: 4000000000   
     -9000000000 quo: 4000000000  
     9000000000 quo: -4000000000  
     -9000000000 quo: -4000000000 
    "

    "Modified: 5.11.1996 / 16:39:36 / cg"
!

\\ aNumber
    "return the remainder of division of the receiver by the argument, aNumber.
     The sign of the result is that of aNumber."

    |abs rem|

    abs := aNumber abs.

    "
     this is the common case, dividing by a SmallInteger.
     Use a special method for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
	(abs between:1 and:16r003fffff) ifTrue:[
	    rem := (self absFastDiv:abs) at:2.
	] ifFalse:[
	    rem := (self absDiv:abs asLargeInteger) at:2
	].
    ] ifFalse:[
	"
	 if the argument is not a largeInteger, coerce
	"
	(aNumber class == self class) ifFalse:[
	    ^ self retry:#\\ coercing:aNumber
	].

	rem := (self absDiv:abs) at:2.
    ].

    aNumber negative ifTrue:[
	^ rem sign:-1
    ].
    ^ rem

    "
     900 \\ 400    
     -900 \\ 400  
     900 \\ -400   
     -900 \\ -400  

     9000000000 \\ 4000000000   
     -9000000000 \\ 4000000000  
     9000000000 \\ -4000000000  
     -9000000000 \\ -4000000000 

     9000000000 \\ 7      
     -9000000000 \\ 7     
     9000000000 \\ -7     
     -9000000000 \\ -7    

     900 rem: 400    
     -900 rem: 400  
     900 rem: -400   
     -900 rem: -400               

     9000000000 rem: 4000000000    
     -9000000000 rem: 4000000000   
     9000000000 rem: -4000000000   
     -9000000000 rem: -4000000000  
    "

    "Modified: 5.11.1996 / 17:10:10 / cg"
!

divMod:aNumber
    "return an array filled with self // aNumber and
     self \\ aNumber.
     The result is only defined for positive receiver and
     argument."

    |otherSign divMod d rem abs "{ Class: SmallInteger }" |

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

    "
     if the argument is not a largeInteger, coerce
    "
    (aNumber class == self class) ifTrue:[
	^ self absDiv:aNumber abs
    ].

    ^ super divMod:aNumber

    "
     9000000000 // 4000000000   => 2

     9000000000 \\ 4000000000   => 1000000000 

     9000000000 divMod: 4000000000   => #(2 1000000000)
    "

    "Modified: 29.10.1996 / 20:44:23 / cg"
    "Created: 29.10.1996 / 21:22:05 / cg"
!

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
!

quo:aNumber
    "return the quotient of the receiver and the argument, aNumber.
     The result is truncated toward zero (which is different from //, which
     truncates toward negative infinity).
     The results sign is negative if the receiver has a sign
     different from the args sign"

    |otherSign d quo abs "{ Class: SmallInteger }" |

    otherSign := aNumber sign.

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

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

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

    "
     900 // 400  
     -900 // 400  
     900 // -400 
     -900 // -400  

     9000000000 // 4000000000     
     -9000000000 // 4000000000    
     9000000000 // -4000000000    
     -9000000000 // -4000000000   

     900 quo: 400    
     -900 quo: 400    
     900 quo: -400  
     -900 quo: -400  

     9000000000 quo: 4000000000   
     -9000000000 quo: 4000000000  
     9000000000 quo: -4000000000  
     -9000000000 quo: -4000000000  
    "

    "Modified: 5.11.1996 / 14:14:17 / cg"
!

rem:aNumber
    "return the remainder of division of the receiver by the argument, aNumber.
     The returned remainder has the same sign as the receiver."

    |rem abs "{ Class: SmallInteger }" |

    "
     this is the common case, dividing by a SmallInteger.
     Use special code for this case ...
    "
    (aNumber class == SmallInteger) ifTrue:[
	abs := aNumber.
	abs := abs abs.
	(abs between:1 and:16r003fffff) ifTrue:[
	    rem := (self absFastDiv:abs) at:2.
	] ifFalse:[
	    rem := (self absDiv:(abs asLargeInteger)) at:2
	].
    ] ifFalse:[
	"
	 if the argument is not a largeInteger, coerce
	"
	(aNumber class == self class) ifFalse:[
	    ^ self retry:#\\ coercing:aNumber
	].

	rem := (self absDiv:aNumber) at:2
    ].

    sign < 0 ifTrue:[
	^ rem sign:-1
    ].
    ^ rem

    "
     900 \\ 400    
     -900 \\ 400   
     900 \\ -400   
     -900 \\ -400  

     9000000000 \\ 4000000000    
     -9000000000 \\ 4000000000   
     9000000000 \\ -4000000000   
     -9000000000 \\ -4000000000  

     900 rem: 400     
     -900 rem: 400    
     900 rem: -400    
     -900 rem: -400   

     9000000000 rem: 4000000000     
     -9000000000 rem: 4000000000    
     9000000000 rem: -4000000000    
     -9000000000 rem: -4000000000   
    "

    "Modified: 5.11.1996 / 14:02:59 / cg"
! !

!LargeInteger methodsFor:'byte access'!

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
!

digitLength
    "return the number bytes used by this Integer"

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

    l := digitByteArray size.
    [l ~~ 0 and:[(digitByteArray at:l) == 0]] whileTrue:[
	l := l - 1.
    ].
    ^ l

    "Modified: 2.2.1996 / 16:47:21 / cg"
!

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

    ^ digitByteArray
! !

!LargeInteger methodsFor:'coercing & converting'!

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

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

    ^ self
!

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
!

coerce:aNumber
    "return the argument as a LargeInteger"

    ^ aNumber asLargeInteger
!

compressed
    "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 }" |

%{  /* NOCONTEXT */
    OBJ t;

    if (__INST(sign) == __MKSMALLINT(0)) {
	RETURN (__MKSMALLINT(0));
    }

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

	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 := digitByteArray size.
    [(index > 0) and:[(digitByteArray at:index) == 0]] whileTrue:[
	index := index - 1
    ].

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

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 := ByteArray with: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
	    ]
	]
    ]

    "Modified: 5.11.1996 / 16:15:39 / cg"
! !

!LargeInteger methodsFor:'comparing'!

< 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 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 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:'double dispatching'!

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

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

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

    "Modified: 20.10.1996 / 18:41:54 / cg"
!

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

    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;

#if defined(i386) /* XXX actually: LSB_FIRST */
	/* max: 0xFFFF * 0xFFFF -> 0xrFFFE0001
	 * + maxCarry (0xFFFF)  -> 0xFFFF0000
	 */

	if (_v <= 0xFFFF) {
	    /* can do it short-wise */
	    while (_l > 1) {
		_prod = ((unsigned short *)digitP)[0] * _v + _carry;
		((unsigned short *)resultP)[0] = _prod & 0xFFFF;
		_carry = _prod >> 16;
		digitP += 2;
		resultP += 2;
		_l -= 2;
	    }
	}
#endif
	{
	    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 compressed
!

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

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

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

    "Modified: 20.10.1996 / 18:41:51 / cg"
! !

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

!LargeInteger methodsFor:'private'!

absDiv:anInteger
    "return an array with two LargeIntegers representing
     abs(self) // abs(theArgument) and abs(self) \\ abs(theArgument).
     Used as a helper for \\, //, rem: and quo:.
     This method needs a rewrite."

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

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

    self = anInteger ifTrue:[
	^ Array with:1 with:0
    ].

    tmp1 := self simpleDeepCopy.
    tmp1 sign:1.
    tmp2 := anInteger simpleDeepCopy.
    tmp2 sign:1.

    (tmp1 < tmp2) ifTrue:[
	^ Array with:0 with:tmp1 
    ].

    count := 0.
    [tmp2 absLess: tmp1] whileTrue:[
	tmp2 mul2.
	count := count + 1
    ].

    tmp2 div2.

    quo := 0 asLargeInteger. 
    quo sign:1.

    [count == 0] whileFalse:[
	quo mul2.
	(tmp1 absLess:tmp2) ifFalse:[
	    quo digits at:1 put:((quo digits at:1) bitOr:1).
	    (tmp1 absSubtract: tmp2) ifFalse:[
		"/ difference is zero; continue shifting
		count := count - 1.
		[count >= 8] whileTrue:[
		    quo mul256.
		    count := count - 8
		].
		[count == 0] whileFalse:[
		    quo mul2.
		    count := count - 1.
		].
		^ Array with:quo compressed with:tmp1 compressed
	    ].
	].
	tmp2 div2.
	count := count - 1
    ].
    ^ Array with:quo compressed with:tmp1 compressed

    "Modified: 5.11.1996 / 18:40:24 / cg"
!

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
!

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

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

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

"This cannot happen (if always normalized)
    self < aPositiveSmallInteger ifTrue:[
	^ Array with:0 with:self
    ].
"
    count := digitByteArray size.
    result := self class basicNew numberOfDigits:count.
    newDigitByteArray := result digits.
    ok := false.
%{
    OBJ __digits;

    __digits = __INST(digitByteArray);

    if (__isByteArray(__digits)
     && __isByteArray(newDigitByteArray)
     && __bothSmallInteger(count, aPositiveSmallInteger)) {
	unsigned int rest = 0;
	int index = __intVal(count);
	int index0;
	unsigned divisor = __intVal(aPositiveSmallInteger);
	unsigned char *digitBytes = __ByteArrayInstPtr(__digits)->ba_element;
	unsigned char *resultBytes = __ByteArrayInstPtr(newDigitByteArray)->ba_element;

	index0 = index;

/*
	if (divisor < 0xFFFF) {
	    while (index > 1) {
		unsigned int t;
		unsigned div;

		index--;
		t = digitBytes[index];
		index--;
		t = (t << 8) | digitBytes[index];
		t = t | (rest << 16);
		div = t / divisor;
		rest = t % divisor;
		resultBytes[index+1] = (div >> 8);
		resultBytes[index] = (div & 0xFF);
	    }
	}
*/
	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;

	/*
	 * no need to normalize ?
	 */
	if ((index0 > 4)
	 && (resultBytes[index0-1])) {
	    RETURN ( __ARRAY_WITH2(result, prevRest));
	}
    }
%}.
    "
     slow code - not normally reached
     (could also do a primitiveFailure here)
    "
    ok ifFalse:[
	self primitiveFailed
    ].

    ^ Array with:result compressed with:prevRest
!

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

    |result resultDigitByteArray lastDigit
     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:(lastDigit := diff).
	index := index + 1
    ].
    [index <= len] whileTrue:[
	resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
	index := index + 1
    ].

    lastDigit == 0 ifTrue:[
	^ result compressed
    ].
    ^ result

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

    "Modified: 5.11.1996 / 14:09:16 / cg"
!

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

    |result resultDigitByteArray lastDigit
     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:(lastDigit := carry bitAnd:16rFF).
	carry := carry bitShift:-8.
	index := index + 1
    ].
    [index <= len] whileTrue:[
	resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
	index := index + 1
    ].

    lastDigit == 0 ifTrue:[
	^ result compressed
    ].
    ^ result

    "Modified: 5.11.1996 / 14:09:19 / cg"
!

absLess:aLargeInteger
    "return true, if abs(self) < abs(theArgument).
     This handles unnormalized largeIntegers."

    |myLen "{ Class: SmallInteger }"
     otherLen "{ Class: SmallInteger }"
     d1   "{ Class: SmallInteger }"
     d2   "{ Class: SmallInteger }"
     otherDigitByteArray |

    myLen := digitByteArray size.
    otherDigitByteArray := aLargeInteger digits.
    otherLen := otherDigitByteArray size.

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

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

    "Modified: 5.11.1996 / 18:37:27 / cg"
!

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

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

    lResult := (len1 max: len2) + 1.
    result := self class basicNew numberOfDigits:lResult.
    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:[
	"/ must generate 255's complement

	result sign:-1.
	[index <= lResult] whileTrue:[
	    resultDigitByteArray basicAt:index put:16rFF.
	    index := index + 1.
	].
	index := resultDigitByteArray size.
	[index > 0] whileTrue:[
	    resultDigitByteArray basicAt:index put:(255 - (resultDigitByteArray at:index)).
	    index := index -1.
	].

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

    "Modified: 5.11.1996 / 14:09:25 / cg"
!

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

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 compressed

    "Modified: 5.11.1996 / 14:09:34 / cg"
!

absSubtract:aLargeInteger
    "destructively subtract aLargeInteger from myself.
     A helper for division; only allowed for positive receiver
     and argument. The receiver must be >= the argument.
     The receiver must be a temporary scratch-number"

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

    len1 := digitByteArray size.
    otherDigitByteArray := aLargeInteger digits.
    len2 := otherDigitByteArray size.
    len2 > len1 ifTrue:[
	[(otherDigitByteArray at:len2) == 0] whileTrue:[
	    len2 := len2 - 1
	].
	len2 > len1 ifTrue:[
	    self halt "/ may not be called that way
	].
    ].

    nonZero := false.
    index := 1.
    borrow := 0.

    done := false.
    [index <= len1] whileTrue:[
	diff := borrow.
	diff := diff + (digitByteArray basicAt:index).
	index <= len2 ifTrue:[
	    diff := diff - (otherDigitByteArray basicAt:index).
	].

	"/ workaround for
	"/ gcc code generator bug

	(diff >= 0) ifTrue:[
	    borrow := 0
	] ifFalse:[
	    borrow := -1.
	    diff := diff + 16r100
	].
	diff ~~ 0 ifTrue:[
	    nonZero := true
	].
	digitByteArray basicAt:index put:diff.
	index := index + 1
    ].
    ^ nonZero

    "Created: 5.11.1996 / 16:23:47 / cg"
    "Modified: 5.11.1996 / 18:56:50 / cg"
!

div2
    "destructively divide the receiver by 2.
     private - used for division only.
     This is worth a primitive."

%{  /* NOCONTEXT */
    OBJ __digits = __INST(digitByteArray);

    if (__isByteArray(__digits)) {
	int __nBytes = __byteArraySize(__digits);
	unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
	unsigned __this, __next;
	int __idx;

	if (__nBytes == 1) {
	    __bp[0] >>= 1;
	    RETURN (self);
	}

	__idx = 1;

	if ((__idx+4) < __nBytes) {
	    __this = ((unsigned long *)__bp)[0];

	    while ((__idx+4) < __nBytes) {
		__next = ((unsigned long *)__bp)[1];
		__this >>= 1;
		__this |= __next << 31;
		((unsigned long *)__bp)[0] = __this;
		__this = __next;
		__bp += 4;
		__idx += 4;
	    }
	}

	__this = __bp[0];
	while (__idx < __nBytes) {
	    __next = __bp[1];
	    __this >>= 1;
	    __this |= __next << 7;
	    __bp[0] = __this;
	    __this = __next;
	    __bp++;
	    __idx++;
	}
	__bp[0] = __this >> 1;
	RETURN (self);
    }
%}.
    self primitiveFailed

    "
     100000 asLargeInteger div2   
    "

    "Modified: 5.11.1996 / 16:12:56 / cg"
!

mul2
    "destructively multiply the receiver by 2.
     private - used for division only.
     This is worth a primitive."

    |nBytes "{ Class: SmallInteger }"
     b      "{ Class: SmallInteger }"
     t|

    nBytes := digitByteArray size.

    b := digitByteArray at:nBytes.
    (b bitAnd:16r80) ~~ 0 ifTrue:[
	"/ need another byte
	nBytes := nBytes + 1.
	t := ByteArray uninitializedNew:nBytes.
	t replaceFrom:1 with:digitByteArray startingAt:1.
	t at:nBytes put:0.
	digitByteArray := t.
    ].

%{
    OBJ __digits = __INST(digitByteArray);

    if (__isByteArray(__digits)) {
	int __nBytes = __intVal(nBytes);
	unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
	unsigned __carry = 0, __newCarry,  __this;
	int __idx;

	while (__nBytes >= 4) {
	    __this = ((unsigned long *)__bp)[0];
	    __newCarry = __this >> 31;
	    ((unsigned long *)__bp)[0] = (__this << 1) | __carry;
	    __carry = __newCarry;
	    __bp += 4;
	    __nBytes -= 4;
	}
	while (__nBytes) {
	    __this = __bp[0];
	    __newCarry = __this >> 7;
	    __bp[0] = (__this << 1) | __carry;
	    __carry = __newCarry;
	    __bp ++;
	    __nBytes--;
	}
	RETURN (self);
    }
%}.
    self primitiveFailed

    "
     100000 asLargeInteger mul2 
    "

    "Modified: 5.11.1996 / 16:37:32 / cg"
!

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

    |newDigits|

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

numberOfDigits:nDigits
"/    digitByteArray := ByteArray uninitializedNew:nDigits.
    digitByteArray := ByteArray new:nDigits.
    sign := 1.
!

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

sign:aNumber
    sign := aNumber
! !

!LargeInteger methodsFor:'testing'!

even
    "return true if the receiver is even"

    ^ (digitByteArray at:1) even
!

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

    ^ (sign < 0)
!

odd
    "return true if the receiver is odd"

    ^ (digitByteArray at:1) odd

    "Modified: 18.11.1996 / 22:19:19 / cg"
!

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

    ^ (sign >= 0)
!

sign
    "return the sign of the receiver"

    ^ sign
!

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

    ^ (sign > 0)
! !

!LargeInteger class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Attic/LargeInt.st,v 1.40 1996-12-19 16:26:17 cg Exp $'
! !