LargeInteger.st
changeset 19135 e2d82660b855
parent 19132 0c0046873268
child 19137 199b5e15b1da
child 19157 5543dd7af087
equal deleted inserted replaced
19134:eaa91cb0ef1b 19135:e2d82660b855
     1 "
     1 "
     2  COPYRIGHT (c) 1994 by Claus Gittinger
     2  COPYRIGHT (c) 1994 by Claus Gittinger
     3 	      All Rights Reserved
     3               All Rights Reserved
     4 
     4 
     5  This software is furnished under a license and may be used
     5  This software is furnished under a license and may be used
     6  only in accordance with the terms of that license and with the
     6  only in accordance with the terms of that license and with the
     7  inclusion of the above copyright notice.   This software may not
     7  inclusion of the above copyright notice.   This software may not
     8  be provided or otherwise made available to, or used by, any
     8  be provided or otherwise made available to, or used by, any
    12 "{ Package: 'stx:libbasic' }"
    12 "{ Package: 'stx:libbasic' }"
    13 
    13 
    14 "{ NameSpace: Smalltalk }"
    14 "{ NameSpace: Smalltalk }"
    15 
    15 
    16 Integer subclass:#LargeInteger
    16 Integer subclass:#LargeInteger
    17 	instanceVariableNames:'sign digitByteArray'
    17         instanceVariableNames:'sign digitByteArray'
    18 	classVariableNames:'UseKarazuba'
    18         classVariableNames:'UseKarazuba'
    19 	poolDictionaries:''
    19         poolDictionaries:''
    20 	category:'Magnitude-Numbers'
    20         category:'Magnitude-Numbers'
    21 !
    21 !
    22 
    22 
    23 !LargeInteger class methodsFor:'documentation'!
    23 !LargeInteger class methodsFor:'documentation'!
    24 
    24 
    25 copyright
    25 copyright
    26 "
    26 "
    27  COPYRIGHT (c) 1994 by Claus Gittinger
    27  COPYRIGHT (c) 1994 by Claus Gittinger
    28 	      All Rights Reserved
    28               All Rights Reserved
    29 
    29 
    30  This software is furnished under a license and may be used
    30  This software is furnished under a license and may be used
    31  only in accordance with the terms of that license and with the
    31  only in accordance with the terms of that license and with the
    32  inclusion of the above copyright notice.   This software may not
    32  inclusion of the above copyright notice.   This software may not
    33  be provided or otherwise made available to, or used by, any
    33  be provided or otherwise made available to, or used by, any
    62     128 bit numbers (which make up almost all instances in practice).
    62     128 bit numbers (which make up almost all instances in practice).
    63     As all of these are transparent to the outside world, any of it may or may not
    63     As all of these are transparent to the outside world, any of it may or may not
    64     change in the future.
    64     change in the future.
    65 
    65 
    66     [author:]
    66     [author:]
    67 	Claus Gittinger
    67         Claus Gittinger
    68 
    68 
    69     [see also:]
    69     [see also:]
    70 	Number
    70         Number
    71 	Float Fraction FixedPoint
    71         Float Fraction FixedPoint
    72 	SmallInteger
    72         SmallInteger
    73 "
    73 "
    74 !
    74 !
    75 
    75 
    76 testing
    76 testing
    77 "
    77 "
    83    v := last := 1.
    83    v := last := 1.
    84    2 to:3000 do:[:i |
    84    2 to:3000 do:[:i |
    85        i printCR.
    85        i printCR.
    86        v := v * i.
    86        v := v * i.
    87        (v / i) ~= last ifTrue:[
    87        (v / i) ~= last ifTrue:[
    88 	   self halt
    88            self halt
    89        ].
    89        ].
    90        last := v.
    90        last := v.
    91    ]
    91    ]
    92 
    92 
    93 
    93 
   255      from the argument, aByteArray."
   255      from the argument, aByteArray."
   256 
   256 
   257     |digits|
   257     |digits|
   258 
   258 
   259     msb == false ifTrue:[
   259     msb == false ifTrue:[
   260 	digits := aByteArrayOfDigits
   260         digits := aByteArrayOfDigits
   261     ] ifFalse:[
   261     ] ifFalse:[
   262 	digits := aByteArrayOfDigits reversed
   262         digits := aByteArrayOfDigits reversed
   263     ].
   263     ].
   264     ^ self basicNew setDigits:digits
   264     ^ self basicNew setDigits:digits
   265 
   265 
   266     "
   266     "
   267      (LargeInteger digitBytes:#[16r10 16r20 16r30 16r00] MSB:false) hexPrintString
   267      (LargeInteger digitBytes:#[16r10 16r20 16r30 16r00] MSB:false) hexPrintString
   300 
   300 
   301 value:aSmallInteger
   301 value:aSmallInteger
   302     "create and return a new LargeInteger with value taken from
   302     "create and return a new LargeInteger with value taken from
   303      the argument, aSmallInteger.
   303      the argument, aSmallInteger.
   304      Notice:
   304      Notice:
   305 	this should be only used internally, since such small
   305         this should be only used internally, since such small
   306 	largeIntegers do not normally occur in the system.
   306         largeIntegers do not normally occur in the system.
   307 	(They are used by myself)
   307         (They are used by myself)
   308      May change/be removed without notice."
   308      May change/be removed without notice."
   309 
   309 
   310     ^ self basicNew value:aSmallInteger
   310     ^ self basicNew value:aSmallInteger
   311 
   311 
   312     "LargeInteger value:3689"
   312     "LargeInteger value:3689"
   337     "
   337     "
   338      this is the common case, multiplying with SmallInteger.
   338      this is the common case, multiplying with SmallInteger.
   339      Use a special method for this case ...
   339      Use a special method for this case ...
   340     "
   340     "
   341     ((numberClass := aNumber class) == SmallInteger) ifTrue:[
   341     ((numberClass := aNumber class) == SmallInteger) ifTrue:[
   342 	^ self productFromInteger:aNumber
   342         ^ self productFromInteger:aNumber
   343     ].
   343     ].
   344 
   344 
   345     "
   345     "
   346      if the argument is not a largeInteger, coerce
   346      if the argument is not a largeInteger, coerce
   347     "
   347     "
   348     (numberClass == self class) ifFalse:[
   348     (numberClass == self class) ifFalse:[
   349 	^ self retry:#* coercing:aNumber
   349         ^ self retry:#* coercing:aNumber
   350     ].
   350     ].
   351 
   351 
   352     otherSign := aNumber sign.
   352     otherSign := aNumber sign.
   353     (sign == otherSign) ifTrue:[^ self absMul:aNumber].
   353     (sign == otherSign) ifTrue:[^ self absMul:aNumber].
   354     (otherSign == 0) ifTrue:[^ 0].
   354     (otherSign == 0) ifTrue:[^ 0].
   365     "
   365     "
   366      this is the common case, adding a SmallInteger.
   366      this is the common case, adding a SmallInteger.
   367      Use a special method for this case ...
   367      Use a special method for this case ...
   368     "
   368     "
   369     ((numberClass := aNumber class) == SmallInteger) ifTrue:[
   369     ((numberClass := aNumber class) == SmallInteger) ifTrue:[
   370 	^ self sumFromInteger:aNumber
   370         ^ self sumFromInteger:aNumber
   371     ].
   371     ].
   372 
   372 
   373     "
   373     "
   374      if the argument is not a largeInteger, coerce
   374      if the argument is not a largeInteger, coerce
   375     "
   375     "
   376     (numberClass == self class) ifFalse:[
   376     (numberClass == self class) ifFalse:[
   377 	^ self retry:#+ coercing:aNumber
   377         ^ self retry:#+ coercing:aNumber
   378     ].
   378     ].
   379 
   379 
   380     otherSign := aNumber sign.
   380     otherSign := aNumber sign.
   381     (sign > 0) ifTrue:[
   381     (sign > 0) ifTrue:[
   382 	"I am positive"
   382         "I am positive"
   383 	(otherSign > 0) ifTrue:[^ self absPlus:aNumber sign:1].
   383         (otherSign > 0) ifTrue:[^ self absPlus:aNumber sign:1].
   384 	(otherSign < 0) ifTrue:[^ self absMinus:aNumber sign:1].
   384         (otherSign < 0) ifTrue:[^ self absMinus:aNumber sign:1].
   385 	^ self
   385         ^ self
   386     ].
   386     ].
   387     "I am negative"
   387     "I am negative"
   388     (otherSign > 0) ifTrue:[^ aNumber absMinus:self sign:1].
   388     (otherSign > 0) ifTrue:[^ aNumber absMinus:self sign:1].
   389     (otherSign < 0) ifTrue:[^ self absPlus:aNumber sign:-1].
   389     (otherSign < 0) ifTrue:[^ self absPlus:aNumber sign:-1].
   390     ^ self
   390     ^ self
   410     "
   410     "
   411      this is the common case, subtracting a SmallInteger.
   411      this is the common case, subtracting a SmallInteger.
   412      Use a special method for this case ...
   412      Use a special method for this case ...
   413     "
   413     "
   414     ((numberClass := aNumber class) == SmallInteger) ifTrue:[
   414     ((numberClass := aNumber class) == SmallInteger) ifTrue:[
   415 	sign > 0 ifTrue:[
   415         sign > 0 ifTrue:[
   416 	    aNumber > 0 ifTrue:[
   416             aNumber > 0 ifTrue:[
   417 		^ self absFastMinus:aNumber sign:1
   417                 ^ self absFastMinus:aNumber sign:1
   418 	    ].
   418             ].
   419 	    ^ self absFastPlus:aNumber sign:1
   419             ^ self absFastPlus:aNumber sign:1
   420 	].
   420         ].
   421 	aNumber > 0 ifTrue:[
   421         aNumber > 0 ifTrue:[
   422 	    ^ self absFastPlus:aNumber sign:-1
   422             ^ self absFastPlus:aNumber sign:-1
   423 	].
   423         ].
   424 	^ self absFastMinus:aNumber sign:-1
   424         ^ self absFastMinus:aNumber sign:-1
   425     ].
   425     ].
   426 
   426 
   427     "
   427     "
   428      if the argument is not a largeInteger, coerce
   428      if the argument is not a largeInteger, coerce
   429     "
   429     "
   430     (numberClass == self class) ifFalse:[
   430     (numberClass == self class) ifFalse:[
   431 	^ self retry:#- coercing:aNumber
   431         ^ self retry:#- coercing:aNumber
   432     ].
   432     ].
   433 
   433 
   434     otherSign := aNumber sign.
   434     otherSign := aNumber sign.
   435     (sign > 0) ifTrue:[
   435     (sign > 0) ifTrue:[
   436 	"I am positive"
   436         "I am positive"
   437 	(otherSign > 0) ifTrue:[
   437         (otherSign > 0) ifTrue:[
   438 	    "+large - +large"
   438             "+large - +large"
   439 	    ^ self absMinus:aNumber sign:1
   439             ^ self absMinus:aNumber sign:1
   440 	].
   440         ].
   441 	(otherSign < 0) ifTrue:[
   441         (otherSign < 0) ifTrue:[
   442 	    "+large - -large"
   442             "+large - -large"
   443 	    ^ self absPlus:aNumber sign:1
   443             ^ self absPlus:aNumber sign:1
   444 	].
   444         ].
   445 	"should not happen"
   445         "should not happen"
   446 	^ self
   446         ^ self
   447     ].
   447     ].
   448     "I am negative"
   448     "I am negative"
   449     (otherSign > 0) ifTrue:[
   449     (otherSign > 0) ifTrue:[
   450 	"-large - +large"
   450         "-large - +large"
   451 	^ self absPlus:aNumber sign:-1
   451         ^ self absPlus:aNumber sign:-1
   452     ].
   452     ].
   453     (otherSign < 0) ifTrue:[
   453     (otherSign < 0) ifTrue:[
   454 	"-large - -large"
   454         "-large - -large"
   455 	^ self absMinus:aNumber sign:-1
   455         ^ self absMinus:aNumber sign:-1
   456     ].
   456     ].
   457     ^ self
   457     ^ self
   458 
   458 
   459     "
   459     "
   460      12345678901234567890 - 0
   460      12345678901234567890 - 0
   476 
   476 
   477 / aNumber
   477 / aNumber
   478     "return the quotient of the receiver and the argument, aNumber"
   478     "return the quotient of the receiver and the argument, aNumber"
   479 
   479 
   480     aNumber isInteger ifTrue:[
   480     aNumber isInteger ifTrue:[
   481 	^ Fraction numerator:self denominator:aNumber
   481         ^ Fraction numerator:self denominator:aNumber
   482     ].
   482     ].
   483     aNumber isFraction ifTrue:[
   483     aNumber isFraction ifTrue:[
   484 	^ Fraction numerator:(self * aNumber denominator) denominator:(aNumber numerator)
   484         ^ Fraction numerator:(self * aNumber denominator) denominator:(aNumber numerator)
   485     ].
   485     ].
   486 
   486 
   487     "this is a q&d hack - we loose lots of precision here ..."
   487     "this is a q&d hack - we loose lots of precision here ..."
   488     ^ (self asFloat / aNumber asFloat)
   488     ^ (self asFloat / aNumber asFloat)
   489 
   489 
   515      Use a special method for this case ...
   515      Use a special method for this case ...
   516     "
   516     "
   517     (cls == SmallInteger) ifTrue:[
   517     (cls == SmallInteger) ifTrue:[
   518         abs := aNumber.
   518         abs := aNumber.
   519         abs := abs abs.
   519         abs := abs abs.
   520         (abs between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffff ifFalse:16r00ffffff)) ifTrue:[
   520         (abs between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r0fffffffffff ifFalse:16r00ffffff)) ifTrue:[
   521             divMod := self absFastDivMod:abs.
   521             divMod := self absFastDivMod:abs.
   522         ] ifFalse:[
   522         ] ifFalse:[
   523             n := abs asLargeInteger.
   523             n := abs asLargeInteger.
   524         ].
   524         ].
   525     ] ifFalse:[
   525     ] ifFalse:[
   582      negative infinity.
   582      negative infinity.
   583      m < |aNumber| AND there is an integer k with (k * aNumber + m) = self
   583      m < |aNumber| AND there is an integer k with (k * aNumber + m) = self
   584 
   584 
   585      The returned remainder has the same sign as aNumber.
   585      The returned remainder has the same sign as aNumber.
   586      The following is always true:
   586      The following is always true:
   587 	(receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
   587         (receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
   588 
   588 
   589      Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
   589      Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
   590      Especially surprising:
   590      Especially surprising:
   591 	-1 \\ 10 -> 9  (because -(1/10) is truncated towards next smaller integer, which is -1,
   591         -1 \\ 10 -> 9  (because -(1/10) is truncated towards next smaller integer, which is -1,
   592 			and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
   592                         and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
   593 	-10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
   593         -10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
   594 			and -4 * 4 gives -12, so we need to add 2 to get the original -10.
   594                         and -4 * 4 gives -12, so we need to add 2 to get the original -10.
   595 
   595 
   596      See #rem: which is the corresponding remainder for division via #quo:.
   596      See #rem: which is the corresponding remainder for division via #quo:.
   597 
   597 
   598      Redefined here for speed."
   598      Redefined here for speed."
   599 
   599 
   600     |abs rem negativeDivisor|
   600     |abs rem negativeDivisor|
   601 
   601 
   602     aNumber negative ifTrue:[
   602     aNumber negative ifTrue:[
   603 	negativeDivisor := true.
   603         negativeDivisor := true.
   604 	abs := aNumber negated.
   604         abs := aNumber negated.
   605     ] ifFalse:[
   605     ] ifFalse:[
   606 	negativeDivisor := false.
   606         negativeDivisor := false.
   607 	abs := aNumber.
   607         abs := aNumber.
   608     ].
   608     ].
   609 
   609 
   610     "
   610     "
   611      this is the common case, dividing by a SmallInteger.
   611      this is the common case, dividing by a SmallInteger.
   612      Use a special method for this case ...
   612      Use a special method for this case ...
   613     "
   613     "
   614     (aNumber class == SmallInteger) ifTrue:[
   614     (aNumber class == SmallInteger) ifTrue:[
   615 	(abs between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffff ifFalse:16r00ffffff)) ifTrue:[
   615         (abs between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffff ifFalse:16r00ffffff)) ifTrue:[
   616 	    rem := (self absFastDivMod:abs) at:2.
   616             rem := (self absFastDivMod:abs) at:2.
   617 	] ifFalse:[
   617         ] ifFalse:[
   618 	    rem := self absMod:abs asLargeInteger
   618             rem := self absMod:abs asLargeInteger
   619 	].
   619         ].
   620     ] ifFalse:[
   620     ] ifFalse:[
   621 	"
   621         "
   622 	 if the argument is not a largeInteger, coerce
   622          if the argument is not a largeInteger, coerce
   623 	"
   623         "
   624 	(aNumber class == self class) ifFalse:[
   624         (aNumber class == self class) ifFalse:[
   625 	    ^ self retry:#\\ coercing:aNumber
   625             ^ self retry:#\\ coercing:aNumber
   626 	].
   626         ].
   627 
   627 
   628 	rem := self absMod:abs.
   628         rem := self absMod:abs.
   629     ].
   629     ].
   630 
   630 
   631     rem = 0 ifFalse:[
   631     rem = 0 ifFalse:[
   632 	negativeDivisor ifTrue:[
   632         negativeDivisor ifTrue:[
   633 	    rem := rem setSign:-1
   633             rem := rem setSign:-1
   634 	].
   634         ].
   635 	(self negative ~~ negativeDivisor) ifTrue:[
   635         (self negative ~~ negativeDivisor) ifTrue:[
   636 	    "different sign, so remainder would have been negative.
   636             "different sign, so remainder would have been negative.
   637 	     rem has been rounded toward zero, this code will simulate
   637              rem has been rounded toward zero, this code will simulate
   638 	     rounding to negative infinity."
   638              rounding to negative infinity."
   639 
   639 
   640 	    rem := aNumber - rem.
   640             rem := aNumber - rem.
   641 	].
   641         ].
   642     ].
   642     ].
   643     ^ rem
   643     ^ rem
   644 
   644 
   645     "
   645     "
   646      (9000000000 \\ 4000000000)   = (900 \\ 400 * 10000000)  ifFalse:[self halt].
   646      (9000000000 \\ 4000000000)   = (900 \\ 400 * 10000000)  ifFalse:[self halt].
   681     "Created: / 26.10.1999 / 21:28:06 / stefan"
   681     "Created: / 26.10.1999 / 21:28:06 / stefan"
   682 !
   682 !
   683 
   683 
   684 divMod:aNumber
   684 divMod:aNumber
   685     "return an array filled with
   685     "return an array filled with
   686 	(self // aNumber) and (self \\ aNumber).
   686         (self // aNumber) and (self \\ aNumber).
   687      The returned remainder has the same sign as aNumber.
   687      The returned remainder has the same sign as aNumber.
   688      The following is always true:
   688      The following is always true:
   689 	(receiver // something) * something + (receiver \\ something) = receiver
   689         (receiver // something) * something + (receiver \\ something) = receiver
   690 
   690 
   691      Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
   691      Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
   692      Especially surprising:
   692      Especially surprising:
   693 	-1 \\ 10 -> 9  (because -(1/10) is truncated towards next smaller integer, which is -1,
   693         -1 \\ 10 -> 9  (because -(1/10) is truncated towards next smaller integer, which is -1,
   694 			and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
   694                         and -1 multiplied by 10 gives -10, so we have to add 9 to get the original -1).
   695 	-10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
   695         -10 \\ 3 -> 2 (because -(10/3) is truncated towards next smaller integer, which is -4,
   696 			and -4 * 4 gives -12, so we need to add 2 to get the original -10.
   696                         and -4 * 4 gives -12, so we need to add 2 to get the original -10.
   697 
   697 
   698      This is redefined here for more performance
   698      This is redefined here for more performance
   699      (as the remainder is generated as a side effect of division)"
   699      (as the remainder is generated as a side effect of division)"
   700 
   700 
   701     |cls n|
   701     |cls n|
   702 
   702 
   703     ((self < 0) or:[aNumber <= 0]) ifTrue:[
   703     ((self < 0) or:[aNumber <= 0]) ifTrue:[
   704 	^ super divMod:aNumber
   704         ^ super divMod:aNumber
   705     ].
   705     ].
   706 
   706 
   707     "/ only handle the common case here
   707     "/ only handle the common case here
   708     cls := aNumber class.
   708     cls := aNumber class.
   709     (cls == SmallInteger) ifTrue:[
   709     (cls == SmallInteger) ifTrue:[
   710 	"
   710         "
   711 	 this is the common case, dividing by a SmallInteger.
   711          this is the common case, dividing by a SmallInteger.
   712 	 Use a special method for this case ...
   712          Use a special method for this case ...
   713 	"
   713         "
   714 	(aNumber between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffff ifFalse:16r00ffffff)) ifTrue:[
   714         (aNumber between:1 and:(SmallInteger maxBytes == 8 ifTrue:16r00ffffffffffff ifFalse:16r00ffffff)) ifTrue:[
   715 	    ^ self absFastDivMod:aNumber abs.
   715             ^ self absFastDivMod:aNumber abs.
   716 	].
   716         ].
   717 	n := aNumber asLargeInteger.
   717         n := aNumber asLargeInteger.
   718     ] ifFalse:[
   718     ] ifFalse:[
   719 	(cls == self class) ifFalse:[
   719         (cls == self class) ifFalse:[
   720 	    ^ super divMod:aNumber
   720             ^ super divMod:aNumber
   721 	].
   721         ].
   722 	n := aNumber.
   722         n := aNumber.
   723     ].
   723     ].
   724 
   724 
   725     ^ self absDivMod:n abs.
   725     ^ self absDivMod:n abs.
   726 
   726 
   727     "
   727     "
   823      The result is truncated toward zero (which is different from //, which
   823      The result is truncated toward zero (which is different from //, which
   824      truncates toward negative infinity).
   824      truncates toward negative infinity).
   825      The results sign is negative if the receiver has a sign
   825      The results sign is negative if the receiver has a sign
   826      different from the args sign.
   826      different from the args sign.
   827      The following is always true:
   827      The following is always true:
   828 	(receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
   828         (receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
   829     "
   829     "
   830 
   830 
   831     |otherSign quo abs "{ Class: SmallInteger }" |
   831     |otherSign quo abs "{ Class: SmallInteger }" |
   832 
   832 
   833     otherSign := aNumber sign.
   833     otherSign := aNumber sign.
   835     "
   835     "
   836      this is the common case, dividing by a SmallInteger.
   836      this is the common case, dividing by a SmallInteger.
   837      Use a special method for this case ...
   837      Use a special method for this case ...
   838     "
   838     "
   839     (aNumber class == SmallInteger) ifTrue:[
   839     (aNumber class == SmallInteger) ifTrue:[
   840 	abs := aNumber.
   840         abs := aNumber.
   841 	abs := abs abs.
   841         abs := abs abs.
   842 	(abs between:1 and:16r00ffffff) ifTrue:[
   842         (abs between:1 and:16r00ffffff) ifTrue:[
   843 	    quo := (self absFastDivMod:abs) at:1.
   843             quo := (self absFastDivMod:abs) at:1.
   844 	    (sign == otherSign) ifTrue:[^ quo].
   844             (sign == otherSign) ifTrue:[^ quo].
   845 	    ^ quo setSign:-1
   845             ^ quo setSign:-1
   846 	]
   846         ]
   847     ].
   847     ].
   848 
   848 
   849     "
   849     "
   850      if the argument is not a largeInteger, coerce
   850      if the argument is not a largeInteger, coerce
   851     "
   851     "
   852     (aNumber class == self class) ifFalse:[
   852     (aNumber class == self class) ifFalse:[
   853 	^ self retry:#quo: coercing:aNumber
   853         ^ self retry:#quo: coercing:aNumber
   854     ].
   854     ].
   855 
   855 
   856     sign < 0 ifTrue:[
   856     sign < 0 ifTrue:[
   857 	(sign == otherSign) ifTrue:[^ (self absDivMod:aNumber negated) at:1].
   857         (sign == otherSign) ifTrue:[^ (self absDivMod:aNumber negated) at:1].
   858     ] ifFalse:[
   858     ] ifFalse:[
   859 	(sign == otherSign) ifTrue:[^ (self absDivMod:aNumber) at:1].
   859         (sign == otherSign) ifTrue:[^ (self absDivMod:aNumber) at:1].
   860     ].
   860     ].
   861     ^ ((self absDivMod:aNumber) at:1) setSign:-1
   861     ^ ((self absDivMod:aNumber) at:1) setSign:-1
   862 
   862 
   863     "
   863     "
   864      900 // 400
   864      900 // 400
   888 
   888 
   889 rem:aNumber
   889 rem:aNumber
   890     "return the remainder of division of the receiver by the argument, aNumber.
   890     "return the remainder of division of the receiver by the argument, aNumber.
   891      The returned remainder has the same sign as the receiver.
   891      The returned remainder has the same sign as the receiver.
   892      The following is always true:
   892      The following is always true:
   893 	(receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
   893         (receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
   894     "
   894     "
   895 
   895 
   896     |rem abs "{ Class: SmallInteger }" |
   896     |rem abs "{ Class: SmallInteger }" |
   897 
   897 
   898     "
   898     "
   899      this is the common case, dividing by a SmallInteger.
   899      this is the common case, dividing by a SmallInteger.
   900      Use special code for this case ...
   900      Use special code for this case ...
   901     "
   901     "
   902     (aNumber class == SmallInteger) ifTrue:[
   902     (aNumber class == SmallInteger) ifTrue:[
   903 	abs := aNumber.
   903         abs := aNumber.
   904 	abs := abs abs.
   904         abs := abs abs.
   905 	(abs between:1 and:16r00ffffff) ifTrue:[
   905         (abs between:1 and:16r00ffffff) ifTrue:[
   906 	    rem := (self absFastDivMod:abs) at:2.
   906             rem := (self absFastDivMod:abs) at:2.
   907 	] ifFalse:[
   907         ] ifFalse:[
   908 	    rem := self absMod:abs asLargeInteger
   908             rem := self absMod:abs asLargeInteger
   909 	].
   909         ].
   910     ] ifFalse:[
   910     ] ifFalse:[
   911 	"
   911         "
   912 	 if the argument is not a largeInteger, coerce
   912          if the argument is not a largeInteger, coerce
   913 	"
   913         "
   914 	(aNumber class == self class) ifFalse:[
   914         (aNumber class == self class) ifFalse:[
   915 	    ^ self retry:#rem coercing:aNumber
   915             ^ self retry:#rem coercing:aNumber
   916 	].
   916         ].
   917 
   917 
   918 	rem := self absMod:aNumber
   918         rem := self absMod:aNumber
   919     ].
   919     ].
   920 
   920 
   921     sign < 0 ifTrue:[
   921     sign < 0 ifTrue:[
   922 	^ rem setSign:-1
   922         ^ rem setSign:-1
   923     ].
   923     ].
   924     ^ rem
   924     ^ rem
   925 
   925 
   926     "
   926     "
   927      900 \\ 400
   927      900 \\ 400
   954 bitAnd:anInteger
   954 bitAnd:anInteger
   955     "return the bitwise-and of the receiver and the argument, anInteger"
   955     "return the bitwise-and of the receiver and the argument, anInteger"
   956 
   956 
   957 %{  /* NOCONTEXT */
   957 %{  /* NOCONTEXT */
   958     if (__isSmallInteger(anInteger)) {
   958     if (__isSmallInteger(anInteger)) {
   959 	INT v2 = __intVal(anInteger);
   959         INT v2 = __intVal(anInteger);
   960 	INT v1;
   960         INT v1;
   961 #if defined(__LSBFIRST__)
   961 #if defined(__LSBFIRST__)
   962 	v1 = *(INT *)(__byteArrayVal(__INST(digitByteArray)));
   962         v1 = *(INT *)(__byteArrayVal(__INST(digitByteArray)));
   963 #else
   963 #else
   964 	unsigned char *digits = (unsigned char *)(__byteArrayVal(__INST(digitByteArray)));
   964         unsigned char *digits = (unsigned char *)(__byteArrayVal(__INST(digitByteArray)));
   965 
   965 
   966 	v1 = digits[0] & 0xFF;
   966         v1 = digits[0] & 0xFF;
   967 	v1 = v1 | ((digits[1] & 0xFF)<<8);
   967         v1 = v1 | ((digits[1] & 0xFF)<<8);
   968 	v1 = v1 | ((digits[2] & 0xFF)<<16);
   968         v1 = v1 | ((digits[2] & 0xFF)<<16);
   969 	v1 = v1 | ((digits[3] & 0xFF)<<24);
   969         v1 = v1 | ((digits[3] & 0xFF)<<24);
   970 # if (__POINTER_SIZE__ == 8)
   970 # if (__POINTER_SIZE__ == 8)
   971 	v1 = v1 | ((digits[4] & 0xFF)<<32);
   971         v1 = v1 | ((digits[4] & 0xFF)<<32);
   972 	v1 = v1 | ((digits[5] & 0xFF)<<40);
   972         v1 = v1 | ((digits[5] & 0xFF)<<40);
   973 	v1 = v1 | ((digits[6] & 0xFF)<<48);
   973         v1 = v1 | ((digits[6] & 0xFF)<<48);
   974 	v1 = v1 | ((digits[7] & 0xFF)<<56);
   974         v1 = v1 | ((digits[7] & 0xFF)<<56);
   975  #endif
   975  #endif
   976 #endif
   976 #endif
   977 	RETURN ( __mkSmallInteger(v1 & v2) );
   977         RETURN ( __mkSmallInteger(v1 & v2) );
   978     }
   978     }
   979 
   979 
   980     if (__isLargeInteger(anInteger)) {
   980     if (__isLargeInteger(anInteger)) {
   981 	OBJ _myDigitByteArray = __INST(digitByteArray);
   981         OBJ _myDigitByteArray = __INST(digitByteArray);
   982 	OBJ _otherDigitByteArray = __LargeIntegerInstPtr(anInteger)->l_digits;
   982         OBJ _otherDigitByteArray = __LargeIntegerInstPtr(anInteger)->l_digits;
   983 
   983 
   984 	if (__isByteArray(_myDigitByteArray)
   984         if (__isByteArray(_myDigitByteArray)
   985 	 && __isByteArray(_otherDigitByteArray)) {
   985          && __isByteArray(_otherDigitByteArray)) {
   986 	    unsigned char *pDigits1, *pDigits2;
   986             unsigned char *pDigits1, *pDigits2;
   987 	    int size1, size2, minSize;
   987             int size1, size2, minSize;
   988 	    union {
   988             union {
   989 		double d;                    // force align
   989                 double d;                    // force align
   990 		unsigned char chars[2048+8];
   990                 unsigned char chars[2048+8];
   991 	    } buffer;
   991             } buffer;
   992 	    unsigned char *pRslt;
   992             unsigned char *pRslt;
   993 	    OBJ newDigits, newLarge;
   993             OBJ newDigits, newLarge;
   994 
   994 
   995 	    pDigits1 = (unsigned char *)(__byteArrayVal(_myDigitByteArray));
   995             pDigits1 = (unsigned char *)(__byteArrayVal(_myDigitByteArray));
   996 	    pDigits2 = (unsigned char *)(__byteArrayVal(_otherDigitByteArray));
   996             pDigits2 = (unsigned char *)(__byteArrayVal(_otherDigitByteArray));
   997 	    pRslt = (void *)(buffer.chars);
   997             pRslt = (void *)(buffer.chars);
   998 
   998 
   999 	    size1 = __byteArraySize(_myDigitByteArray);
   999             size1 = __byteArraySize(_myDigitByteArray);
  1000 	    size2 = __byteArraySize(_otherDigitByteArray);
  1000             size2 = __byteArraySize(_otherDigitByteArray);
  1001 	    minSize = (size1 < size2) ? size1 : size2;
  1001             minSize = (size1 < size2) ? size1 : size2;
  1002 	    if (minSize <= sizeof(buffer.chars)) {
  1002             if (minSize <= sizeof(buffer.chars)) {
  1003 		int n = minSize;
  1003                 int n = minSize;
  1004 
  1004 
  1005 	    /* not worth it - but a nice try and first testbed for mmx... */
  1005             /* not worth it - but a nice try and first testbed for mmx... */
  1006 #define x__USE_MMX__
  1006 #define x__USE_MMX__
  1007 #ifdef __USE_MMX__
  1007 #ifdef __USE_MMX__
  1008 #ifdef __VISUALC__
  1008 #ifdef __VISUALC__
  1009 		if (((INT)pRslt & 7) == 0) {    // 8-byte aligned
  1009                 if (((INT)pRslt & 7) == 0) {    // 8-byte aligned
  1010 		    if (((INT)pDigits1 & 7) == ((INT)pDigits2 & 7)) {   // same align
  1010                     if (((INT)pDigits1 & 7) == ((INT)pDigits2 & 7)) {   // same align
  1011 			while (((INT)pDigits1 & 7) && (n >= sizeof(int))) {
  1011                         while (((INT)pDigits1 & 7) && (n >= sizeof(int))) {
  1012 			    ((int *)pRslt)[0] = ((int *)pDigits1)[0] & ((int *)pDigits2)[0];
  1012                             ((int *)pRslt)[0] = ((int *)pDigits1)[0] & ((int *)pDigits2)[0];
  1013 			    pRslt += sizeof(int);
  1013                             pRslt += sizeof(int);
  1014 			    pDigits1 += sizeof(int);
  1014                             pDigits1 += sizeof(int);
  1015 			    pDigits2 += sizeof(int);
  1015                             pDigits2 += sizeof(int);
  1016 			    pDigits2 += sizeof(int);
  1016                             pDigits2 += sizeof(int);
  1017 			    n -= sizeof(int);
  1017                             n -= sizeof(int);
  1018 			}
  1018                         }
  1019 			for (; n >= 8; n -= 8) {
  1019                         for (; n >= 8; n -= 8) {
  1020 			    __asm {
  1020                             __asm {
  1021 				mov eax, pDigits1
  1021                                 mov eax, pDigits1
  1022 				movq mm0, [eax]
  1022                                 movq mm0, [eax]
  1023 				mov eax, pDigits2
  1023                                 mov eax, pDigits2
  1024 				movq mm1, [eax]
  1024                                 movq mm1, [eax]
  1025 				pand mm0, mm1
  1025                                 pand mm0, mm1
  1026 				mov eax, pRslt
  1026                                 mov eax, pRslt
  1027 				movq [eax], mm0
  1027                                 movq [eax], mm0
  1028 			    }
  1028                             }
  1029 			    pDigits1 += 8;
  1029                             pDigits1 += 8;
  1030 			    pDigits2 += 8;
  1030                             pDigits2 += 8;
  1031 			    pRslt += 8;
  1031                             pRslt += 8;
  1032 			}
  1032                         }
  1033 			__asm {
  1033                         __asm {
  1034 			    emms ; switch back to FPU state.
  1034                             emms ; switch back to FPU state.
  1035 			}
  1035                         }
  1036 		    }
  1036                     }
  1037 		}
  1037                 }
  1038 #endif /* __VISUALC__ */
  1038 #endif /* __VISUALC__ */
  1039 #endif /* __USE_MMX__ */
  1039 #endif /* __USE_MMX__ */
  1040 
  1040 
  1041 		for (; n >= sizeof(INT)*4; n -= sizeof(INT)*4) {
  1041                 for (; n >= sizeof(INT)*4; n -= sizeof(INT)*4) {
  1042 		    ((INT *)pRslt)[0] = ((INT *)pDigits1)[0] & ((INT *)pDigits2)[0];
  1042                     ((INT *)pRslt)[0] = ((INT *)pDigits1)[0] & ((INT *)pDigits2)[0];
  1043 		    ((INT *)pRslt)[1] = ((INT *)pDigits1)[1] & ((INT *)pDigits2)[1];
  1043                     ((INT *)pRslt)[1] = ((INT *)pDigits1)[1] & ((INT *)pDigits2)[1];
  1044 		    ((INT *)pRslt)[2] = ((INT *)pDigits1)[2] & ((INT *)pDigits2)[2];
  1044                     ((INT *)pRslt)[2] = ((INT *)pDigits1)[2] & ((INT *)pDigits2)[2];
  1045 		    ((INT *)pRslt)[3] = ((INT *)pDigits1)[3] & ((INT *)pDigits2)[3];
  1045                     ((INT *)pRslt)[3] = ((INT *)pDigits1)[3] & ((INT *)pDigits2)[3];
  1046 		    pRslt += sizeof(INT)*4;
  1046                     pRslt += sizeof(INT)*4;
  1047 		    pDigits1 += sizeof(INT)*4;
  1047                     pDigits1 += sizeof(INT)*4;
  1048 		    pDigits2 += sizeof(INT)*4;
  1048                     pDigits2 += sizeof(INT)*4;
  1049 		}
  1049                 }
  1050 		for (; n >= sizeof(INT); n -= sizeof(INT)) {
  1050                 for (; n >= sizeof(INT); n -= sizeof(INT)) {
  1051 		    ((INT *)pRslt)[0] = ((INT *)pDigits1)[0] & ((INT *)pDigits2)[0];
  1051                     ((INT *)pRslt)[0] = ((INT *)pDigits1)[0] & ((INT *)pDigits2)[0];
  1052 		    pRslt += sizeof(INT);
  1052                     pRslt += sizeof(INT);
  1053 		    pDigits1 += sizeof(INT);
  1053                     pDigits1 += sizeof(INT);
  1054 		    pDigits2 += sizeof(INT);
  1054                     pDigits2 += sizeof(INT);
  1055 		}
  1055                 }
  1056 		for (; n > 0; n--) {
  1056                 for (; n > 0; n--) {
  1057 		    *pRslt = *pDigits1 & *pDigits2;
  1057                     *pRslt = *pDigits1 & *pDigits2;
  1058 		    pRslt++;
  1058                     pRslt++;
  1059 		    pDigits1++;
  1059                     pDigits1++;
  1060 		    pDigits2++;
  1060                     pDigits2++;
  1061 		}
  1061                 }
  1062 		// normalize
  1062                 // normalize
  1063 		while ((pRslt[-1]==0) && (pRslt > buffer.chars)) {
  1063                 while ((pRslt[-1]==0) && (pRslt > buffer.chars)) {
  1064 		    pRslt--;
  1064                     pRslt--;
  1065 		}
  1065                 }
  1066 
  1066 
  1067 		// allocate result
  1067                 // allocate result
  1068 		n = pRslt-buffer.chars;
  1068                 n = pRslt-buffer.chars;
  1069 		if (n <= sizeof(INT)) {
  1069                 if (n <= sizeof(INT)) {
  1070 		    INT val = 0;
  1070                     INT val = 0;
  1071 
  1071 
  1072 		    // make it a smallInteger / 32bitInteger
  1072                     // make it a smallInteger / 32bitInteger
  1073 		    while (n > 0) {
  1073                     while (n > 0) {
  1074 			val = (val << 8) + buffer.chars[--n];
  1074                         val = (val << 8) + buffer.chars[--n];
  1075 		    }
  1075                     }
  1076 		    RETURN (__MKUINT(val));
  1076                     RETURN (__MKUINT(val));
  1077 		}
  1077                 }
  1078 		newDigits = __MKBYTEARRAY(buffer.chars, n);
  1078                 newDigits = __MKBYTEARRAY(buffer.chars, n);
  1079 		if (newDigits) {
  1079                 if (newDigits) {
  1080 		    __PROTECT__(newDigits);
  1080                     __PROTECT__(newDigits);
  1081 		    newLarge = __STX___new(sizeof(struct __LargeInteger));
  1081                     newLarge = __STX___new(sizeof(struct __LargeInteger));
  1082 		    __UNPROTECT__(newDigits);
  1082                     __UNPROTECT__(newDigits);
  1083 		    if (newLarge) {
  1083                     if (newLarge) {
  1084 			__InstPtr(newLarge)->o_class = LargeInteger; __STORE(newLarge, LargeInteger);
  1084                         __InstPtr(newLarge)->o_class = LargeInteger; __STORE(newLarge, LargeInteger);
  1085 			__LargeIntegerInstPtr(newLarge)->l_digits = newDigits; __STORE(newLarge, newDigits);
  1085                         __LargeIntegerInstPtr(newLarge)->l_digits = newDigits; __STORE(newLarge, newDigits);
  1086 			__LargeIntegerInstPtr(newLarge)->l_sign = __MKSMALLINT(1);
  1086                         __LargeIntegerInstPtr(newLarge)->l_sign = __MKSMALLINT(1);
  1087 			RETURN (newLarge);
  1087                         RETURN (newLarge);
  1088 		    }
  1088                     }
  1089 		}
  1089                 }
  1090 	    }
  1090             }
  1091 	}
  1091         }
  1092     }
  1092     }
  1093 %}.
  1093 %}.
  1094     ^ super bitAnd:anInteger
  1094     ^ super bitAnd:anInteger
  1095 
  1095 
  1096     "
  1096     "
  1115     |len1 len2 newBytes|
  1115     |len1 len2 newBytes|
  1116 
  1116 
  1117     anInteger class ~~ LargeInteger ifTrue:[^ super bitXor:anInteger].
  1117     anInteger class ~~ LargeInteger ifTrue:[^ super bitXor:anInteger].
  1118 
  1118 
  1119     (len1 := anInteger digitLength) > (len2 := self digitLength) ifTrue:[
  1119     (len1 := anInteger digitLength) > (len2 := self digitLength) ifTrue:[
  1120 	newBytes := anInteger digitBytes copy.
  1120         newBytes := anInteger digitBytes copy.
  1121 	newBytes bitXorBytesFrom:1 to:len2 with:digitByteArray startingAt:1
  1121         newBytes bitXorBytesFrom:1 to:len2 with:digitByteArray startingAt:1
  1122     ] ifFalse:[
  1122     ] ifFalse:[
  1123 	newBytes := digitByteArray copy.
  1123         newBytes := digitByteArray copy.
  1124 	newBytes bitXorBytesFrom:1 to:len1 with:anInteger digits startingAt:1
  1124         newBytes bitXorBytesFrom:1 to:len1 with:anInteger digits startingAt:1
  1125     ].
  1125     ].
  1126     ^ (self class digitBytes:newBytes) compressed
  1126     ^ (self class digitBytes:newBytes) compressed
  1127 
  1127 
  1128     "
  1128     "
  1129      (16r112233445566778899 bitXor:16rFF                ) printStringRadix:16 '112233445566778866'
  1129      (16r112233445566778899 bitXor:16rFF                ) printStringRadix:16 '112233445566778866'
  1134      |bigNum1 bigNum2|
  1134      |bigNum1 bigNum2|
  1135 
  1135 
  1136      bigNum1 := 2 raisedToInteger:512.
  1136      bigNum1 := 2 raisedToInteger:512.
  1137      bigNum2 := 2 raisedToInteger:510.
  1137      bigNum2 := 2 raisedToInteger:510.
  1138      Time millisecondsToRun:[
  1138      Time millisecondsToRun:[
  1139 	1000000 timesRepeat:[
  1139         1000000 timesRepeat:[
  1140 	   bigNum1 bitXor:bigNum2.
  1140            bigNum1 bitXor:bigNum2.
  1141 	]
  1141         ]
  1142      ]
  1142      ]
  1143     "
  1143     "
  1144 !
  1144 !
  1145 
  1145 
  1146 lowBit
  1146 lowBit
  1162 
  1162 
  1163     /*
  1163     /*
  1164      * quickly advance over full 0-words
  1164      * quickly advance over full 0-words
  1165      */
  1165      */
  1166     if (__isByteArray(__digitByteArray)) {
  1166     if (__isByteArray(__digitByteArray)) {
  1167 	int __sz = __byteArraySize(__digitByteArray);
  1167         int __sz = __byteArraySize(__digitByteArray);
  1168 	unsigned char *__bP = __byteArrayVal(__digitByteArray);
  1168         unsigned char *__bP = __byteArrayVal(__digitByteArray);
  1169 	unsigned char *__bP0 = __bP;
  1169         unsigned char *__bP0 = __bP;
  1170 
  1170 
  1171 	sz = __MKSMALLINT(__sz);
  1171         sz = __MKSMALLINT(__sz);
  1172 
  1172 
  1173 #ifdef __UNROLL_LOOPS__
  1173 #ifdef __UNROLL_LOOPS__
  1174 	while (__sz > (sizeof(INT) * 4)) {
  1174         while (__sz > (sizeof(INT) * 4)) {
  1175 	    if (( ((INT *)__bP)[0]
  1175             if (( ((INT *)__bP)[0]
  1176 		 | ((INT *)__bP)[1]
  1176                  | ((INT *)__bP)[1]
  1177 		 | ((INT *)__bP)[2]
  1177                  | ((INT *)__bP)[2]
  1178 		 | ((INT *)__bP)[3] ) != 0) break;
  1178                  | ((INT *)__bP)[3] ) != 0) break;
  1179 	    __sz -= sizeof(INT) * 4;
  1179             __sz -= sizeof(INT) * 4;
  1180 	    __bP += sizeof(INT) * 4;
  1180             __bP += sizeof(INT) * 4;
  1181 	}
  1181         }
  1182 #endif
  1182 #endif
  1183 	while (__sz > sizeof(INT)) {
  1183         while (__sz > sizeof(INT)) {
  1184 	    if ( ((INT *)__bP)[0] != 0 ) break;
  1184             if ( ((INT *)__bP)[0] != 0 ) break;
  1185 	    __sz -= sizeof(INT);
  1185             __sz -= sizeof(INT);
  1186 	    __bP += sizeof(INT);
  1186             __bP += sizeof(INT);
  1187 	}
  1187         }
  1188 	while (__sz > 0) {
  1188         while (__sz > 0) {
  1189 	    unsigned int c;
  1189             unsigned int c;
  1190 
  1190 
  1191 	    if ( (c = *__bP) != 0 ) {
  1191             if ( (c = *__bP) != 0 ) {
  1192 		int bitIdx = (__bP - __bP0) * 8;
  1192                 int bitIdx = (__bP - __bP0) * 8;
  1193 #ifdef __BSF
  1193 #ifdef __BSF
  1194 		{
  1194                 {
  1195 		    int index;
  1195                     int index;
  1196 		    int t = c;
  1196                     int t = c;
  1197 
  1197 
  1198 		    index = __BSF(t);
  1198                     index = __BSF(t);
  1199 		    RETURN ( __mkSmallInteger(index + 1 + bitIdx) );
  1199                     RETURN ( __mkSmallInteger(index + 1 + bitIdx) );
  1200 		}
  1200                 }
  1201 #else
  1201 #else
  1202 		if (c & 0x0F) {
  1202                 if (c & 0x0F) {
  1203 		    if (c & 0x03) {
  1203                     if (c & 0x03) {
  1204 			if (c & 0x01) {
  1204                         if (c & 0x01) {
  1205 			    RETURN ( __mkSmallInteger( bitIdx + 1) );
  1205                             RETURN ( __mkSmallInteger( bitIdx + 1) );
  1206 			} else {
  1206                         } else {
  1207 			    RETURN ( __mkSmallInteger( bitIdx + 2) );
  1207                             RETURN ( __mkSmallInteger( bitIdx + 2) );
  1208 			}
  1208                         }
  1209 		    } else {
  1209                     } else {
  1210 			if (c & 0x04) {
  1210                         if (c & 0x04) {
  1211 			    RETURN ( __mkSmallInteger( bitIdx + 3) );
  1211                             RETURN ( __mkSmallInteger( bitIdx + 3) );
  1212 			} else {
  1212                         } else {
  1213 			    RETURN ( __mkSmallInteger( bitIdx + 4) );
  1213                             RETURN ( __mkSmallInteger( bitIdx + 4) );
  1214 			}
  1214                         }
  1215 		    }
  1215                     }
  1216 		} else {
  1216                 } else {
  1217 		    if (c & 0x30) {
  1217                     if (c & 0x30) {
  1218 			if (c & 0x10) {
  1218                         if (c & 0x10) {
  1219 			    RETURN ( __mkSmallInteger( bitIdx + 5) );
  1219                             RETURN ( __mkSmallInteger( bitIdx + 5) );
  1220 			} else {
  1220                         } else {
  1221 			    RETURN ( __mkSmallInteger( bitIdx + 6) );
  1221                             RETURN ( __mkSmallInteger( bitIdx + 6) );
  1222 			}
  1222                         }
  1223 		    } else {
  1223                     } else {
  1224 			if (c & 0x40) {
  1224                         if (c & 0x40) {
  1225 			    RETURN ( __mkSmallInteger( bitIdx + 7) );
  1225                             RETURN ( __mkSmallInteger( bitIdx + 7) );
  1226 			} else {
  1226                         } else {
  1227 			    RETURN ( __mkSmallInteger( bitIdx + 8) );
  1227                             RETURN ( __mkSmallInteger( bitIdx + 8) );
  1228 			}
  1228                         }
  1229 		    }
  1229                     }
  1230 		}
  1230                 }
  1231 #endif
  1231 #endif
  1232 		break;
  1232                 break;
  1233 	    }
  1233             }
  1234 	    __sz--;
  1234             __sz--;
  1235 	    __bP++;
  1235             __bP++;
  1236 	}
  1236         }
  1237 	idx0 = __mkSmallInteger( __bP - __bP0 + 1 );
  1237         idx0 = __mkSmallInteger( __bP - __bP0 + 1 );
  1238     }
  1238     }
  1239 %}.
  1239 %}.
  1240 
  1240 
  1241     "/ never actually reached
  1241     "/ never actually reached
  1242     idx0 to:sz do:[:digitIndex |
  1242     idx0 to:sz do:[:digitIndex |
  1243 	(byte := digitByteArray at:digitIndex) ~~ 0 ifTrue:[
  1243         (byte := digitByteArray at:digitIndex) ~~ 0 ifTrue:[
  1244 	    ^ (digitIndex-1)*8 + (byte lowBit)
  1244             ^ (digitIndex-1)*8 + (byte lowBit)
  1245 	]
  1245         ]
  1246     ].
  1246     ].
  1247     ^ 0 "/ should not happen
  1247     ^ 0 "/ should not happen
  1248 
  1248 
  1249     "
  1249     "
  1250      (1 bitShift:0) lowBit
  1250      (1 bitShift:0) lowBit
  1264      (1 bitShift:1000) highBit
  1264      (1 bitShift:1000) highBit
  1265      ((1 bitShift:64)-1) lowBit
  1265      ((1 bitShift:64)-1) lowBit
  1266      ((1 bitShift:64)-1) highBit
  1266      ((1 bitShift:64)-1) highBit
  1267 
  1267 
  1268      1 to:1000 do:[:idx |
  1268      1 to:1000 do:[:idx |
  1269 	self assert:(( 1 bitShift:idx) lowBit = (idx+1)).
  1269         self assert:(( 1 bitShift:idx) lowBit = (idx+1)).
  1270 	self assert:(( 1 bitShift:idx) lowBit = ( 1 bitShift:idx) highBit).
  1270         self assert:(( 1 bitShift:idx) lowBit = ( 1 bitShift:idx) highBit).
  1271 	self assert:(( 3 bitShift:idx) lowBit = (idx+1)).
  1271         self assert:(( 3 bitShift:idx) lowBit = (idx+1)).
  1272 	self assert:(( 7 bitShift:idx) lowBit = (idx+1)).
  1272         self assert:(( 7 bitShift:idx) lowBit = (idx+1)).
  1273 	self assert:(( 15 bitShift:idx) lowBit = (idx+1)).
  1273         self assert:(( 15 bitShift:idx) lowBit = (idx+1)).
  1274 	self assert:(( 31 bitShift:idx) lowBit = (idx+1)).
  1274         self assert:(( 31 bitShift:idx) lowBit = (idx+1)).
  1275 	self assert:(( 63 bitShift:idx) lowBit = (idx+1)).
  1275         self assert:(( 63 bitShift:idx) lowBit = (idx+1)).
  1276 	self assert:(( 127 bitShift:idx) lowBit = (idx+1)).
  1276         self assert:(( 127 bitShift:idx) lowBit = (idx+1)).
  1277 	self assert:(( 255 bitShift:idx) lowBit = (idx+1)).
  1277         self assert:(( 255 bitShift:idx) lowBit = (idx+1)).
  1278      ]
  1278      ]
  1279 
  1279 
  1280      |num|
  1280      |num|
  1281 
  1281 
  1282      num := (1 bitShift:1000).
  1282      num := (1 bitShift:1000).
  1283      Time millisecondsToRun:[
  1283      Time millisecondsToRun:[
  1284 	1000000 timesRepeat:[
  1284         1000000 timesRepeat:[
  1285 	    num lowBit
  1285             num lowBit
  1286 	]
  1286         ]
  1287      ]
  1287      ]
  1288     "
  1288     "
  1289 
  1289 
  1290     "Modified: 14.8.1997 / 11:55:34 / cg"
  1290     "Modified: 14.8.1997 / 11:55:34 / cg"
  1291 ! !
  1291 ! !
  1293 !LargeInteger methodsFor:'bit operators - indexed'!
  1293 !LargeInteger methodsFor:'bit operators - indexed'!
  1294 
  1294 
  1295 bitAt:anIntegerIndex
  1295 bitAt:anIntegerIndex
  1296     "return the value of the index's bit (index starts at 1) as 0 or 1.
  1296     "return the value of the index's bit (index starts at 1) as 0 or 1.
  1297      Notice: the result of bitAt: on negative receivers is not
  1297      Notice: the result of bitAt: on negative receivers is not
  1298 	     defined in the language standard (since the implementation
  1298              defined in the language standard (since the implementation
  1299 	     is free to choose any internal representation for integers)"
  1299              is free to choose any internal representation for integers)"
  1300 
  1300 
  1301 %{  /* NOCONTEXT */
  1301 %{  /* NOCONTEXT */
  1302     if (__isSmallInteger(anIntegerIndex)) {
  1302     if (__isSmallInteger(anIntegerIndex)) {
  1303 	INT idx = __smallIntegerVal(anIntegerIndex) - 1;
  1303         INT idx = __smallIntegerVal(anIntegerIndex) - 1;
  1304 
  1304 
  1305 	if (idx >= 0) {
  1305         if (idx >= 0) {
  1306 	    int v1;
  1306             int v1;
  1307 	    int byteOffset = idx / 8;
  1307             int byteOffset = idx / 8;
  1308 	    int digitLen   = __byteArraySize(__INST(digitByteArray));
  1308             int digitLen   = __byteArraySize(__INST(digitByteArray));
  1309 
  1309 
  1310 	    if (digitLen < byteOffset) {
  1310             if (digitLen < byteOffset) {
  1311 		RETURN(__mkSmallInteger(0));
  1311                 RETURN(__mkSmallInteger(0));
  1312 	    }
  1312             }
  1313 
  1313 
  1314 	    v1 = (__byteArrayVal(__INST(digitByteArray)))[byteOffset];
  1314             v1 = (__byteArrayVal(__INST(digitByteArray)))[byteOffset];
  1315 	    if (v1 & (1 << (idx % 8))) {
  1315             if (v1 & (1 << (idx % 8))) {
  1316 		RETURN(__mkSmallInteger(1));
  1316                 RETURN(__mkSmallInteger(1));
  1317 	    } else {
  1317             } else {
  1318 		RETURN(__mkSmallInteger(0));
  1318                 RETURN(__mkSmallInteger(0));
  1319 	    }
  1319             }
  1320 	}
  1320         }
  1321     }
  1321     }
  1322 %}.
  1322 %}.
  1323     ^ super bitAt:anIntegerIndex
  1323     ^ super bitAt:anIntegerIndex
  1324 
  1324 
  1325     "
  1325     "
  1343      but a new number is returned. Should be named #withBitSet:"
  1343      but a new number is returned. Should be named #withBitSet:"
  1344 
  1344 
  1345     |myDigitLength newDigitLength newDigitBytes byteIndexOfBitToSet|
  1345     |myDigitLength newDigitLength newDigitBytes byteIndexOfBitToSet|
  1346 
  1346 
  1347     index <= 0 ifTrue:[
  1347     index <= 0 ifTrue:[
  1348 	^ SubscriptOutOfBoundsSignal
  1348         ^ SubscriptOutOfBoundsSignal
  1349 		raiseRequestWith:index
  1349                 raiseRequestWith:index
  1350 		errorString:'index out of bounds'
  1350                 errorString:'index out of bounds'
  1351     ].
  1351     ].
  1352 
  1352 
  1353     myDigitLength := digitByteArray size.
  1353     myDigitLength := digitByteArray size.
  1354     byteIndexOfBitToSet := ((index-1)//8)+1.
  1354     byteIndexOfBitToSet := ((index-1)//8)+1.
  1355     byteIndexOfBitToSet > myDigitLength ifTrue:[
  1355     byteIndexOfBitToSet > myDigitLength ifTrue:[
  1356 	newDigitLength := myDigitLength max:byteIndexOfBitToSet.
  1356         newDigitLength := myDigitLength max:byteIndexOfBitToSet.
  1357 	newDigitBytes := ByteArray new:newDigitLength.
  1357         newDigitBytes := ByteArray new:newDigitLength.
  1358 	newDigitBytes replaceFrom:1 to:myDigitLength with:digitByteArray startingAt:1.
  1358         newDigitBytes replaceFrom:1 to:myDigitLength with:digitByteArray startingAt:1.
  1359     ] ifFalse:[
  1359     ] ifFalse:[
  1360 	newDigitBytes := digitByteArray copy
  1360         newDigitBytes := digitByteArray copy
  1361     ].
  1361     ].
  1362     newDigitBytes
  1362     newDigitBytes
  1363 	at:byteIndexOfBitToSet
  1363         at:byteIndexOfBitToSet
  1364 	put:((newDigitBytes at:byteIndexOfBitToSet) setBit:(((index-1)\\8)+1)).
  1364         put:((newDigitBytes at:byteIndexOfBitToSet) setBit:(((index-1)\\8)+1)).
  1365     ^ self class digitBytes:newDigitBytes sign:sign
  1365     ^ self class digitBytes:newDigitBytes sign:sign
  1366 
  1366 
  1367     "
  1367     "
  1368      TestCase assert:( 16r80000000 setBit:3  ) = 16r80000004
  1368      TestCase assert:( 16r80000000 setBit:3  ) = 16r80000004
  1369      TestCase assert:( 16r80000000 setBit:33 ) = 16r180000000
  1369      TestCase assert:( 16r80000000 setBit:33 ) = 16r180000000
  1406 
  1406 
  1407     unsigned INT bits;
  1407     unsigned INT bits;
  1408     int count;
  1408     int count;
  1409 
  1409 
  1410     if (__isSmallInteger(shiftCount)) {
  1410     if (__isSmallInteger(shiftCount)) {
  1411 	count = __intVal(shiftCount);
  1411         count = __intVal(shiftCount);
  1412 	count = count % 32;
  1412         count = count % 32;
  1413 
  1413 
  1414 	bits = __unsignedLongIntVal(self);
  1414         bits = __unsignedLongIntVal(self);
  1415 	if (count > 0) {
  1415         if (count > 0) {
  1416 	    bits = (bits << count) | (bits >> (32-count));
  1416             bits = (bits << count) | (bits >> (32-count));
  1417 	} else {
  1417         } else {
  1418 	    bits = (bits >> (-count)) | (bits << (32-(-count)));
  1418             bits = (bits >> (-count)) | (bits << (32-(-count)));
  1419 	}
  1419         }
  1420 #if __POINTER_SIZE__ == 8
  1420 #if __POINTER_SIZE__ == 8
  1421 	bits &= 0xFFFFFFFFL;
  1421         bits &= 0xFFFFFFFFL;
  1422 #endif
  1422 #endif
  1423 	RETURN (__MKUINT(bits));
  1423         RETURN (__MKUINT(bits));
  1424     }
  1424     }
  1425 %}.
  1425 %}.
  1426     ^ self primitiveFailed
  1426     ^ self primitiveFailed
  1427 
  1427 
  1428     "
  1428     "
  1444 
  1444 
  1445     unsigned INT bits;
  1445     unsigned INT bits;
  1446     int count;
  1446     int count;
  1447 
  1447 
  1448     if (__isSmallInteger(shiftCount)) {
  1448     if (__isSmallInteger(shiftCount)) {
  1449 	count = __intVal(shiftCount);
  1449         count = __intVal(shiftCount);
  1450 	if (count >= 32) {
  1450         if (count >= 32) {
  1451 	    RETURN (__mkSmallInteger(0));
  1451             RETURN (__mkSmallInteger(0));
  1452 	}
  1452         }
  1453 
  1453 
  1454 	bits = __unsignedLongIntVal(self);
  1454         bits = __unsignedLongIntVal(self);
  1455 	if (count > 0) {
  1455         if (count > 0) {
  1456 	    bits = bits << count;
  1456             bits = bits << count;
  1457 	} else {
  1457         } else {
  1458 	    bits = bits >> (-count);
  1458             bits = bits >> (-count);
  1459 	}
  1459         }
  1460 #if __POINTER_SIZE__ == 8
  1460 #if __POINTER_SIZE__ == 8
  1461 	bits &= 0xFFFFFFFFL;
  1461         bits &= 0xFFFFFFFFL;
  1462 #endif
  1462 #endif
  1463 	RETURN (__MKUINT(bits));
  1463         RETURN (__MKUINT(bits));
  1464     }
  1464     }
  1465 %}.
  1465 %}.
  1466     ^ self primitiveFailed
  1466     ^ self primitiveFailed
  1467 
  1467 
  1468     "
  1468     "
  1714     return context._RETURN( STInteger._new( ((STLargeInteger)self).digitLength() ));
  1714     return context._RETURN( STInteger._new( ((STLargeInteger)self).digitLength() ));
  1715 #endif
  1715 #endif
  1716 %}.
  1716 %}.
  1717     l := digitByteArray size.
  1717     l := digitByteArray size.
  1718     [l ~~ 0 and:[(digitByteArray at:l) == 0]] whileTrue:[
  1718     [l ~~ 0 and:[(digitByteArray at:l) == 0]] whileTrue:[
  1719 	l := l - 1.
  1719         l := l - 1.
  1720     ].
  1720     ].
  1721     ^ l
  1721     ^ l
  1722 
  1722 
  1723     "Modified: 31.7.1997 / 13:18:28 / cg"
  1723     "Modified: 31.7.1997 / 13:18:28 / cg"
  1724 !
  1724 !
  1816 
  1816 
  1817 %{  /* NOCONTEXT */
  1817 %{  /* NOCONTEXT */
  1818     OBJ t;
  1818     OBJ t;
  1819 
  1819 
  1820     if (__INST(sign) == __mkSmallInteger(0)) {
  1820     if (__INST(sign) == __mkSmallInteger(0)) {
  1821 	RETURN (__mkSmallInteger(0));
  1821         RETURN (__mkSmallInteger(0));
  1822     }
  1822     }
  1823 
  1823 
  1824     t = __INST(digitByteArray);
  1824     t = __INST(digitByteArray);
  1825     if (__isByteArray(t)) {
  1825     if (__isByteArray(t)) {
  1826 	unsigned char *__digitBytes = __ByteArrayInstPtr(t)->ba_element;
  1826         unsigned char *__digitBytes = __ByteArrayInstPtr(t)->ba_element;
  1827 	int _idx, _idx0;
  1827         int _idx, _idx0;
  1828 	INT _val;
  1828         INT _val;
  1829 
  1829 
  1830 	_idx = _idx0 = __byteArraySize(t);
  1830         _idx = _idx0 = __byteArraySize(t);
  1831 	while ((_idx > 0) && (__digitBytes[_idx - 1] == 0)) {
  1831         while ((_idx > 0) && (__digitBytes[_idx - 1] == 0)) {
  1832 	    _idx--;
  1832             _idx--;
  1833 	}
  1833         }
  1834 #if __POINTER_SIZE__ == 8
  1834 #if __POINTER_SIZE__ == 8
  1835 	switch (_idx) {
  1835         switch (_idx) {
  1836 	    case 8:
  1836             case 8:
  1837 		_val = __digitBytes[7];
  1837                 _val = __digitBytes[7];
  1838 		if (_val <= 0x40) {
  1838                 if (_val <= 0x40) {
  1839 		    _val = (_val<<8);
  1839                     _val = (_val<<8);
  1840 		    _val = (_val + __digitBytes[6]) << 8;
  1840                     _val = (_val + __digitBytes[6]) << 8;
  1841 		    _val = (_val + __digitBytes[5]) << 8;
  1841                     _val = (_val + __digitBytes[5]) << 8;
  1842 		    _val = (_val + __digitBytes[4]) << 8;
  1842                     _val = (_val + __digitBytes[4]) << 8;
  1843 		    _val = (_val + __digitBytes[3]) << 8;
  1843                     _val = (_val + __digitBytes[3]) << 8;
  1844 		    _val = (_val + __digitBytes[2]) << 8;
  1844                     _val = (_val + __digitBytes[2]) << 8;
  1845 		    _val = (_val + __digitBytes[1]) << 8;
  1845                     _val = (_val + __digitBytes[1]) << 8;
  1846 		    _val += __digitBytes[0];
  1846                     _val += __digitBytes[0];
  1847 		    if (__INST(sign) == __mkSmallInteger(-1))
  1847                     if (__INST(sign) == __mkSmallInteger(-1))
  1848 			_val = -_val;
  1848                         _val = -_val;
  1849 		    if (__ISVALIDINTEGER(_val)) {
  1849                     if (__ISVALIDINTEGER(_val)) {
  1850 			RETURN (__mkSmallInteger(_val));
  1850                         RETURN (__mkSmallInteger(_val));
  1851 		    }
  1851                     }
  1852 		}
  1852                 }
  1853 		break;
  1853                 break;
  1854 	    case 7:
  1854             case 7:
  1855 # if defined(__LSBFIRST__)
  1855 # if defined(__LSBFIRST__)
  1856 		_val = ((INT *)__digitBytes)[0] & 0x00FFFFFFFFFFFFFFL;
  1856                 _val = ((INT *)__digitBytes)[0] & 0x00FFFFFFFFFFFFFFL;
  1857 # else
  1857 # else
  1858 		_val = (__digitBytes[6]<<8);
  1858                 _val = (__digitBytes[6]<<8);
  1859 		_val = (_val + __digitBytes[5]) << 8;
  1859                 _val = (_val + __digitBytes[5]) << 8;
  1860 		_val = (_val + __digitBytes[4]) << 8;
  1860                 _val = (_val + __digitBytes[4]) << 8;
  1861 		_val = (_val + __digitBytes[3]) << 8;
  1861                 _val = (_val + __digitBytes[3]) << 8;
  1862 		_val = (_val + __digitBytes[2]) << 8;
  1862                 _val = (_val + __digitBytes[2]) << 8;
  1863 		_val = (_val + __digitBytes[1]) << 8;
  1863                 _val = (_val + __digitBytes[1]) << 8;
  1864 		_val += __digitBytes[0];
  1864                 _val += __digitBytes[0];
  1865 # endif
  1865 # endif
  1866 		if (__INST(sign) == __mkSmallInteger(-1))
  1866                 if (__INST(sign) == __mkSmallInteger(-1))
  1867 		    _val = -_val;
  1867                     _val = -_val;
  1868 		RETURN (__mkSmallInteger(_val));
  1868                 RETURN (__mkSmallInteger(_val));
  1869 	    case 6:
  1869             case 6:
  1870 # if defined(__LSBFIRST__)
  1870 # if defined(__LSBFIRST__)
  1871 		_val = ((INT *)__digitBytes)[0] & 0x0000FFFFFFFFFFFFL;
  1871                 _val = ((INT *)__digitBytes)[0] & 0x0000FFFFFFFFFFFFL;
  1872 # else
  1872 # else
  1873 		_val = (__digitBytes[5]<<8);
  1873                 _val = (__digitBytes[5]<<8);
  1874 		_val = (_val + __digitBytes[4]) << 8;
  1874                 _val = (_val + __digitBytes[4]) << 8;
  1875 		_val = (_val + __digitBytes[3]) << 8;
  1875                 _val = (_val + __digitBytes[3]) << 8;
  1876 		_val = (_val + __digitBytes[2]) << 8;
  1876                 _val = (_val + __digitBytes[2]) << 8;
  1877 		_val = (_val + __digitBytes[1]) << 8;
  1877                 _val = (_val + __digitBytes[1]) << 8;
  1878 		_val += __digitBytes[0];
  1878                 _val += __digitBytes[0];
  1879 # endif
  1879 # endif
  1880 		if (__INST(sign) == __mkSmallInteger(-1))
  1880                 if (__INST(sign) == __mkSmallInteger(-1))
  1881 		    _val = -_val;
  1881                     _val = -_val;
  1882 		RETURN (__mkSmallInteger(_val));
  1882                 RETURN (__mkSmallInteger(_val));
  1883 	    case 5:
  1883             case 5:
  1884 # if defined(__LSBFIRST__)
  1884 # if defined(__LSBFIRST__)
  1885 		_val = ((INT *)__digitBytes)[0] & 0x000000FFFFFFFFFFL;
  1885                 _val = ((INT *)__digitBytes)[0] & 0x000000FFFFFFFFFFL;
  1886 # else
  1886 # else
  1887 		_val = (__digitBytes[4]<<8);
  1887                 _val = (__digitBytes[4]<<8);
  1888 		_val = (_val + __digitBytes[3]) << 8;
  1888                 _val = (_val + __digitBytes[3]) << 8;
  1889 		_val = (_val + __digitBytes[2]) << 8;
  1889                 _val = (_val + __digitBytes[2]) << 8;
  1890 		_val = (_val + __digitBytes[1]) << 8;
  1890                 _val = (_val + __digitBytes[1]) << 8;
  1891 		_val += __digitBytes[0];
  1891                 _val += __digitBytes[0];
  1892 # endif
  1892 # endif
  1893 		if (__INST(sign) == __mkSmallInteger(-1))
  1893                 if (__INST(sign) == __mkSmallInteger(-1))
  1894 		    _val = -_val;
  1894                     _val = -_val;
  1895 		RETURN (__mkSmallInteger(_val));
  1895                 RETURN (__mkSmallInteger(_val));
  1896 	    case 4:
  1896             case 4:
  1897 # if defined(__LSBFIRST__)
  1897 # if defined(__LSBFIRST__)
  1898 		_val = ((INT *)__digitBytes)[0] & 0x00000000FFFFFFFFL;
  1898                 _val = ((INT *)__digitBytes)[0] & 0x00000000FFFFFFFFL;
  1899 # else
  1899 # else
  1900 		_val = (__digitBytes[3]<<8);
  1900                 _val = (__digitBytes[3]<<8);
  1901 		_val = (_val + __digitBytes[2]) << 8;
  1901                 _val = (_val + __digitBytes[2]) << 8;
  1902 		_val = (_val + __digitBytes[1]) << 8;
  1902                 _val = (_val + __digitBytes[1]) << 8;
  1903 		_val += __digitBytes[0];
  1903                 _val += __digitBytes[0];
  1904 # endif
  1904 # endif
  1905 		if (__INST(sign) == __mkSmallInteger(-1))
  1905                 if (__INST(sign) == __mkSmallInteger(-1))
  1906 		    _val = -_val;
  1906                     _val = -_val;
  1907 		RETURN (__mkSmallInteger(_val));
  1907                 RETURN (__mkSmallInteger(_val));
  1908 	    case 3:
  1908             case 3:
  1909 # if defined(__LSBFIRST__)
  1909 # if defined(__LSBFIRST__)
  1910 		_val = ((int *)__digitBytes)[0] & 0x00FFFFFF;
  1910                 _val = ((int *)__digitBytes)[0] & 0x00FFFFFF;
  1911 # else
  1911 # else
  1912 		_val = (__digitBytes[2]<<8);
  1912                 _val = (__digitBytes[2]<<8);
  1913 		_val = (_val + __digitBytes[1]) << 8;
  1913                 _val = (_val + __digitBytes[1]) << 8;
  1914 		_val += __digitBytes[0];
  1914                 _val += __digitBytes[0];
  1915 # endif
  1915 # endif
  1916 		if (__INST(sign) == __mkSmallInteger(-1))
  1916                 if (__INST(sign) == __mkSmallInteger(-1))
  1917 		    _val = -_val;
  1917                     _val = -_val;
  1918 		RETURN (__mkSmallInteger(_val));
  1918                 RETURN (__mkSmallInteger(_val));
  1919 	    case 2:
  1919             case 2:
  1920 # if defined(__LSBFIRST__)
  1920 # if defined(__LSBFIRST__)
  1921 		_val = ((int *)__digitBytes)[0] & 0x0000FFFF;
  1921                 _val = ((int *)__digitBytes)[0] & 0x0000FFFF;
  1922 # else
  1922 # else
  1923 		_val = (__digitBytes[1]<<8) + __digitBytes[0];
  1923                 _val = (__digitBytes[1]<<8) + __digitBytes[0];
  1924 # endif
  1924 # endif
  1925 		if (__INST(sign) == __mkSmallInteger(-1))
  1925                 if (__INST(sign) == __mkSmallInteger(-1))
  1926 		    _val = -_val;
  1926                     _val = -_val;
  1927 		RETURN (__mkSmallInteger(_val));
  1927                 RETURN (__mkSmallInteger(_val));
  1928 	    case 1:
  1928             case 1:
  1929 		_val = __digitBytes[0];
  1929                 _val = __digitBytes[0];
  1930 		if (__INST(sign) == __mkSmallInteger(-1))
  1930                 if (__INST(sign) == __mkSmallInteger(-1))
  1931 		    _val = -_val;
  1931                     _val = -_val;
  1932 		RETURN (__mkSmallInteger(_val));
  1932                 RETURN (__mkSmallInteger(_val));
  1933 	    case 0:
  1933             case 0:
  1934 		RETURN (__mkSmallInteger(0));
  1934                 RETURN (__mkSmallInteger(0));
  1935 
  1935 
  1936 	}
  1936         }
  1937 #else
  1937 #else
  1938 	if (_idx <= 4) {
  1938         if (_idx <= 4) {
  1939 	    if (_idx <= 2) {
  1939             if (_idx <= 2) {
  1940 		if (_idx == 0) {
  1940                 if (_idx == 0) {
  1941 		    RETURN (__mkSmallInteger(0));
  1941                     RETURN (__mkSmallInteger(0));
  1942 		}
  1942                 }
  1943 		if (_idx == 1) {
  1943                 if (_idx == 1) {
  1944 		    _val = __digitBytes[0];
  1944                     _val = __digitBytes[0];
  1945 		    if (__INST(sign) == __mkSmallInteger(-1))
  1945                     if (__INST(sign) == __mkSmallInteger(-1))
  1946 			_val = -_val;
  1946                         _val = -_val;
  1947 		    RETURN (__mkSmallInteger(_val));
  1947                     RETURN (__mkSmallInteger(_val));
  1948 		}
  1948                 }
  1949 # if defined(__LSBFIRST__)
  1949 # if defined(__LSBFIRST__)
  1950 		_val = ((int *)__digitBytes)[0] & 0x0000FFFF;
  1950                 _val = ((int *)__digitBytes)[0] & 0x0000FFFF;
  1951 # else
  1951 # else
  1952 		_val = (__digitBytes[1]<<8) + __digitBytes[0];
  1952                 _val = (__digitBytes[1]<<8) + __digitBytes[0];
  1953 # endif
  1953 # endif
  1954 		if (__INST(sign) == __mkSmallInteger(-1))
  1954                 if (__INST(sign) == __mkSmallInteger(-1))
  1955 		    _val = -_val;
  1955                     _val = -_val;
  1956 		RETURN (__mkSmallInteger(_val));
  1956                 RETURN (__mkSmallInteger(_val));
  1957 	    }
  1957             }
  1958 	    if (_idx == 3) {
  1958             if (_idx == 3) {
  1959 # if defined(__LSBFIRST__)
  1959 # if defined(__LSBFIRST__)
  1960 		_val = ((int *)__digitBytes)[0] & 0x00FFFFFF;
  1960                 _val = ((int *)__digitBytes)[0] & 0x00FFFFFF;
  1961 # else
  1961 # else
  1962 		_val = (((__digitBytes[2]<<8) + __digitBytes[1])<<8) + __digitBytes[0];
  1962                 _val = (((__digitBytes[2]<<8) + __digitBytes[1])<<8) + __digitBytes[0];
  1963 # endif
  1963 # endif
  1964 		if (__INST(sign) == __mkSmallInteger(-1))
  1964                 if (__INST(sign) == __mkSmallInteger(-1))
  1965 		    _val = -_val;
  1965                     _val = -_val;
  1966 		RETURN (__mkSmallInteger(_val));
  1966                 RETURN (__mkSmallInteger(_val));
  1967 	    }
  1967             }
  1968 	    _val = __digitBytes[3];
  1968             _val = __digitBytes[3];
  1969 	    if (_val <= 0x40) {
  1969             if (_val <= 0x40) {
  1970 # if defined(__LSBFIRST__)
  1970 # if defined(__LSBFIRST__)
  1971 		_val = ((int *)__digitBytes)[0];
  1971                 _val = ((int *)__digitBytes)[0];
  1972 # else
  1972 # else
  1973 		_val = (((((_val<<8) + __digitBytes[2])<<8) + __digitBytes[1])<<8) + __digitBytes[0];
  1973                 _val = (((((_val<<8) + __digitBytes[2])<<8) + __digitBytes[1])<<8) + __digitBytes[0];
  1974 # endif
  1974 # endif
  1975 		if (__INST(sign) == __mkSmallInteger(-1))
  1975                 if (__INST(sign) == __mkSmallInteger(-1))
  1976 		    _val = -_val;
  1976                     _val = -_val;
  1977 		if (__ISVALIDINTEGER(_val)) {
  1977                 if (__ISVALIDINTEGER(_val)) {
  1978 		    RETURN (__mkSmallInteger(_val));
  1978                     RETURN (__mkSmallInteger(_val));
  1979 		}
  1979                 }
  1980 	    }
  1980             }
  1981 	}
  1981         }
  1982 #endif
  1982 #endif
  1983 
  1983 
  1984 	if (_idx == _idx0) {
  1984         if (_idx == _idx0) {
  1985 	    RETURN (self);
  1985             RETURN (self);
  1986 	}
  1986         }
  1987 
  1987 
  1988 	/*
  1988         /*
  1989 	 * must copy & cut off some (zero)bytes
  1989          * must copy & cut off some (zero)bytes
  1990 	 */
  1990          */
  1991 	{
  1991         {
  1992 	    OBJ newDigits;
  1992             OBJ newDigits;
  1993 	    OBJ oldDigits;
  1993             OBJ oldDigits;
  1994 
  1994 
  1995 	    /*
  1995             /*
  1996 	     * careful - there is no context here to protect
  1996              * careful - there is no context here to protect
  1997 	     * the receiver ...
  1997              * the receiver ...
  1998 	     */
  1998              */
  1999 	    __PROTECT__(self);
  1999             __PROTECT__(self);
  2000 	    __PROTECT__(__INST(digitByteArray));
  2000             __PROTECT__(__INST(digitByteArray));
  2001 	    newDigits = __BYTEARRAY_UNINITIALIZED_NEW_INT(_idx);
  2001             newDigits = __BYTEARRAY_UNINITIALIZED_NEW_INT(_idx);
  2002 	    __UNPROTECT__(oldDigits);
  2002             __UNPROTECT__(oldDigits);
  2003 	    __UNPROTECT__(self);
  2003             __UNPROTECT__(self);
  2004 	    if (newDigits) {
  2004             if (newDigits) {
  2005 		bcopy(__ByteArrayInstPtr(oldDigits)->ba_element,
  2005                 bcopy(__ByteArrayInstPtr(oldDigits)->ba_element,
  2006 		      __ByteArrayInstPtr(newDigits)->ba_element,
  2006                       __ByteArrayInstPtr(newDigits)->ba_element,
  2007 		      _idx);
  2007                       _idx);
  2008 		__INST(digitByteArray) = newDigits; __STORE(self, newDigits);
  2008                 __INST(digitByteArray) = newDigits; __STORE(self, newDigits);
  2009 		RETURN (self);
  2009                 RETURN (self);
  2010 	    }
  2010             }
  2011 	    /*
  2011             /*
  2012 	     * allocation failed ...
  2012              * allocation failed ...
  2013 	     * ... fall through to trigger the error
  2013              * ... fall through to trigger the error
  2014 	     */
  2014              */
  2015 	}
  2015         }
  2016     }
  2016     }
  2017 %}.
  2017 %}.
  2018     index0 := index := digitByteArray size.
  2018     index0 := index := digitByteArray size.
  2019     [(index > 0) and:[(digitByteArray at:index) == 0]] whileTrue:[
  2019     [(index > 0) and:[(digitByteArray at:index) == 0]] whileTrue:[
  2020 	index := index - 1
  2020         index := index - 1
  2021     ].
  2021     ].
  2022 "/    ((index < SmallInteger maxBytes)
  2022 "/    ((index < SmallInteger maxBytes)
  2023 "/    or:[(index == SmallInteger maxBytes)
  2023 "/    or:[(index == SmallInteger maxBytes)
  2024 "/            and:[(digitByteArray at:index) < 16r20]])
  2024 "/            and:[(digitByteArray at:index) < 16r20]])
  2025 "/    ifTrue:[
  2025 "/    ifTrue:[
  2029 "/            val := val bitOr:(digitByteArray at:i).
  2029 "/            val := val bitOr:(digitByteArray at:i).
  2030 "/        ].
  2030 "/        ].
  2031 "/        ^ val * sign
  2031 "/        ^ val * sign
  2032 "/    ].
  2032 "/    ].
  2033     (index ~~ index0) ifTrue:[
  2033     (index ~~ index0) ifTrue:[
  2034 	digitByteArray := digitByteArray copyFrom:1 to:index
  2034         digitByteArray := digitByteArray copyFrom:1 to:index
  2035     ].
  2035     ].
  2036     ^ self
  2036     ^ self
  2037 !
  2037 !
  2038 
  2038 
  2039 generality
  2039 generality
  2070      could have simply created a 4-byte largeinteger and normalize it.
  2070      could have simply created a 4-byte largeinteger and normalize it.
  2071      The code below does the normalize right away, avoiding the
  2071      The code below does the normalize right away, avoiding the
  2072      overhead of producing any intermediate byte-arrays (and the scanning)
  2072      overhead of producing any intermediate byte-arrays (and the scanning)
  2073     "
  2073     "
  2074     (aSmallInteger == 0) ifTrue: [
  2074     (aSmallInteger == 0) ifTrue: [
  2075 	digitByteArray := ByteArray with:0.
  2075         digitByteArray := ByteArray with:0.
  2076 	sign := 0.
  2076         sign := 0.
  2077 	^ self
  2077         ^ self
  2078     ].
  2078     ].
  2079 
  2079 
  2080     (aSmallInteger < 0) ifTrue: [
  2080     (aSmallInteger < 0) ifTrue: [
  2081 	sign := -1.
  2081         sign := -1.
  2082 	absValue := aSmallInteger negated
  2082         absValue := aSmallInteger negated
  2083     ] ifFalse: [
  2083     ] ifFalse: [
  2084 	sign := 1.
  2084         sign := 1.
  2085 	absValue := aSmallInteger
  2085         absValue := aSmallInteger
  2086     ].
  2086     ].
  2087 
  2087 
  2088     b1 := absValue bitAnd:16rFF.
  2088     b1 := absValue bitAnd:16rFF.
  2089     absValue := absValue bitShift:-8.
  2089     absValue := absValue bitShift:-8.
  2090     absValue == 0 ifTrue:[
  2090     absValue == 0 ifTrue:[
  2091 	digitByteArray := ByteArray with:b1
  2091         digitByteArray := ByteArray with:b1
  2092     ] ifFalse:[
  2092     ] ifFalse:[
  2093 	b2 := absValue bitAnd:16rFF.
  2093         b2 := absValue bitAnd:16rFF.
  2094 	absValue := absValue bitShift:-8.
  2094         absValue := absValue bitShift:-8.
  2095 	absValue == 0 ifTrue:[
  2095         absValue == 0 ifTrue:[
  2096 	    digitByteArray := ByteArray with:b1 with:b2
  2096             digitByteArray := ByteArray with:b1 with:b2
  2097 	] ifFalse:[
  2097         ] ifFalse:[
  2098 	    b3 := absValue bitAnd:16rFF.
  2098             b3 := absValue bitAnd:16rFF.
  2099 	    absValue := absValue bitShift:-8.
  2099             absValue := absValue bitShift:-8.
  2100 	    absValue == 0 ifTrue:[
  2100             absValue == 0 ifTrue:[
  2101 		digitByteArray := ByteArray with:b1 with:b2 with:b3
  2101                 digitByteArray := ByteArray with:b1 with:b2 with:b3
  2102 	    ] ifFalse:[
  2102             ] ifFalse:[
  2103 		b4 := absValue bitAnd:16rFF.
  2103                 b4 := absValue bitAnd:16rFF.
  2104 		absValue := absValue bitShift:-8.
  2104                 absValue := absValue bitShift:-8.
  2105 		absValue == 0 ifTrue:[
  2105                 absValue == 0 ifTrue:[
  2106 		    digitByteArray := ByteArray with:b1 with:b2 with:b3 with:b4
  2106                     digitByteArray := ByteArray with:b1 with:b2 with:b3 with:b4
  2107 		] ifFalse:[
  2107                 ] ifFalse:[
  2108 		    b5 := absValue bitAnd:16rFF.
  2108                     b5 := absValue bitAnd:16rFF.
  2109 		    absValue := absValue bitShift:-8.
  2109                     absValue := absValue bitShift:-8.
  2110 		    absValue == 0 ifTrue:[
  2110                     absValue == 0 ifTrue:[
  2111 			digitByteArray := ByteArray new:5.
  2111                         digitByteArray := ByteArray new:5.
  2112 			digitByteArray at:1 put:b1.
  2112                         digitByteArray at:1 put:b1.
  2113 			digitByteArray at:2 put:b2.
  2113                         digitByteArray at:2 put:b2.
  2114 			digitByteArray at:3 put:b3.
  2114                         digitByteArray at:3 put:b3.
  2115 			digitByteArray at:4 put:b4.
  2115                         digitByteArray at:4 put:b4.
  2116 			digitByteArray at:5 put:b5.
  2116                         digitByteArray at:5 put:b5.
  2117 		    ] ifFalse:[
  2117                     ] ifFalse:[
  2118 			b6 := absValue bitAnd:16rFF.
  2118                         b6 := absValue bitAnd:16rFF.
  2119 			absValue := absValue bitShift:-8.
  2119                         absValue := absValue bitShift:-8.
  2120 			absValue == 0 ifTrue:[
  2120                         absValue == 0 ifTrue:[
  2121 			    digitByteArray := ByteArray new:6.
  2121                             digitByteArray := ByteArray new:6.
  2122 			    digitByteArray at:1 put:b1.
  2122                             digitByteArray at:1 put:b1.
  2123 			    digitByteArray at:2 put:b2.
  2123                             digitByteArray at:2 put:b2.
  2124 			    digitByteArray at:3 put:b3.
  2124                             digitByteArray at:3 put:b3.
  2125 			    digitByteArray at:4 put:b4.
  2125                             digitByteArray at:4 put:b4.
  2126 			    digitByteArray at:5 put:b5.
  2126                             digitByteArray at:5 put:b5.
  2127 			    digitByteArray at:6 put:b6.
  2127                             digitByteArray at:6 put:b6.
  2128 			] ifFalse:[
  2128                         ] ifFalse:[
  2129 			    b7 := absValue bitAnd:16rFF.
  2129                             b7 := absValue bitAnd:16rFF.
  2130 			    absValue := absValue bitShift:-8.
  2130                             absValue := absValue bitShift:-8.
  2131 			    absValue == 0 ifTrue:[
  2131                             absValue == 0 ifTrue:[
  2132 				digitByteArray := ByteArray new:7.
  2132                                 digitByteArray := ByteArray new:7.
  2133 				digitByteArray at:1 put:b1.
  2133                                 digitByteArray at:1 put:b1.
  2134 				digitByteArray at:2 put:b2.
  2134                                 digitByteArray at:2 put:b2.
  2135 				digitByteArray at:3 put:b3.
  2135                                 digitByteArray at:3 put:b3.
  2136 				digitByteArray at:4 put:b4.
  2136                                 digitByteArray at:4 put:b4.
  2137 				digitByteArray at:5 put:b5.
  2137                                 digitByteArray at:5 put:b5.
  2138 				digitByteArray at:6 put:b6.
  2138                                 digitByteArray at:6 put:b6.
  2139 				digitByteArray at:7 put:b7.
  2139                                 digitByteArray at:7 put:b7.
  2140 			    ] ifFalse:[
  2140                             ] ifFalse:[
  2141 				digitByteArray := ByteArray new:8.
  2141                                 digitByteArray := ByteArray new:8.
  2142 				digitByteArray at:1 put:b1.
  2142                                 digitByteArray at:1 put:b1.
  2143 				digitByteArray at:2 put:b2.
  2143                                 digitByteArray at:2 put:b2.
  2144 				digitByteArray at:3 put:b3.
  2144                                 digitByteArray at:3 put:b3.
  2145 				digitByteArray at:4 put:b4.
  2145                                 digitByteArray at:4 put:b4.
  2146 				digitByteArray at:5 put:b5.
  2146                                 digitByteArray at:5 put:b5.
  2147 				digitByteArray at:6 put:b6.
  2147                                 digitByteArray at:6 put:b6.
  2148 				digitByteArray at:7 put:b7.
  2148                                 digitByteArray at:7 put:b7.
  2149 				digitByteArray at:8 put:absValue.
  2149                                 digitByteArray at:8 put:absValue.
  2150 			    ]
  2150                             ]
  2151 			]
  2151                         ]
  2152 		    ]
  2152                     ]
  2153 		]
  2153                 ]
  2154 	    ]
  2154             ]
  2155 	]
  2155         ]
  2156     ]
  2156     ]
  2157 
  2157 
  2158     "Modified: / 26.5.1999 / 22:18:14 / cg"
  2158     "Modified: / 26.5.1999 / 22:18:14 / cg"
  2159 ! !
  2159 ! !
  2160 
  2160 
  2164     "return true, if the argument, aNumber is greater than the receiver"
  2164     "return true, if the argument, aNumber is greater than the receiver"
  2165 
  2165 
  2166     |otherSign|
  2166     |otherSign|
  2167 
  2167 
  2168     (aNumber class == self class) ifTrue:[
  2168     (aNumber class == self class) ifTrue:[
  2169 	otherSign := aNumber sign.
  2169         otherSign := aNumber sign.
  2170 
  2170 
  2171 	(sign > 0) ifTrue:[
  2171         (sign > 0) ifTrue:[
  2172 	    "I am positive"
  2172             "I am positive"
  2173 	    (otherSign > 0) ifTrue:[^ self absLess:aNumber].
  2173             (otherSign > 0) ifTrue:[^ self absLess:aNumber].
  2174 	    ^ false "aNumber is <= 0"
  2174             ^ false "aNumber is <= 0"
  2175 	].
  2175         ].
  2176 	"I am negative"
  2176         "I am negative"
  2177 	(otherSign > 0) ifTrue:[^ true].
  2177         (otherSign > 0) ifTrue:[^ true].
  2178 	(otherSign == 0) ifTrue:[^ true].
  2178         (otherSign == 0) ifTrue:[^ true].
  2179 	^ (aNumber absLess:self)
  2179         ^ (aNumber absLess:self)
  2180     ].
  2180     ].
  2181     (aNumber class == SmallInteger) ifTrue:[
  2181     (aNumber class == SmallInteger) ifTrue:[
  2182 	otherSign := aNumber sign.
  2182         otherSign := aNumber sign.
  2183 
  2183 
  2184 	(sign > 0) ifTrue:[
  2184         (sign > 0) ifTrue:[
  2185 	    "I am positive"
  2185             "I am positive"
  2186 	    ^ false "aNumber is <= 0"
  2186             ^ false "aNumber is <= 0"
  2187 	].
  2187         ].
  2188 	(sign == 0) ifTrue:[
  2188         (sign == 0) ifTrue:[
  2189 	    (otherSign > 0) ifTrue:[^ true].
  2189             (otherSign > 0) ifTrue:[^ true].
  2190 	    ^ false
  2190             ^ false
  2191 	].
  2191         ].
  2192 	"I am negative"
  2192         "I am negative"
  2193 	^ true
  2193         ^ true
  2194     ].
  2194     ].
  2195     "/ hack for epsilon tests
  2195     "/ hack for epsilon tests
  2196     (aNumber class == Float) ifTrue:[
  2196     (aNumber class == Float) ifTrue:[
  2197 	self negative ifTrue:[
  2197         self negative ifTrue:[
  2198 	    "/ I am a large negative; so my value is definitely below SmallInteger minVal
  2198             "/ I am a large negative; so my value is definitely below SmallInteger minVal
  2199 	    aNumber >= SmallInteger minVal asFloat ifTrue:[^ true].
  2199             aNumber >= SmallInteger minVal asFloat ifTrue:[^ true].
  2200 	] ifFalse:[
  2200         ] ifFalse:[
  2201 	    "/ I am a large positive; so my value is definitely above SmallInteger maxVal
  2201             "/ I am a large positive; so my value is definitely above SmallInteger maxVal
  2202 	    aNumber <= SmallInteger maxVal asFloat ifTrue:[^ false].
  2202             aNumber <= SmallInteger maxVal asFloat ifTrue:[^ false].
  2203 	].
  2203         ].
  2204     ].
  2204     ].
  2205 
  2205 
  2206     ^ aNumber lessFromInteger:self
  2206     ^ aNumber lessFromInteger:self
  2207 
  2207 
  2208     "Modified: / 31.7.2002 / 10:08:19 / cg"
  2208     "Modified: / 31.7.2002 / 10:08:19 / cg"
  2213      as the receiver, false otherwise"
  2213      as the receiver, false otherwise"
  2214 
  2214 
  2215     "/ speed up compare to 0
  2215     "/ speed up compare to 0
  2216 
  2216 
  2217     (aNumber == 0) ifTrue:[
  2217     (aNumber == 0) ifTrue:[
  2218 	^ sign == 0
  2218         ^ sign == 0
  2219     ].
  2219     ].
  2220 
  2220 
  2221     (aNumber class == self class) ifFalse:[
  2221     (aNumber class == self class) ifFalse:[
  2222 	"/
  2222         "/
  2223 	"/ here, we depend on the fact, that largeinteger
  2223         "/ here, we depend on the fact, that largeinteger
  2224 	"/ results are always converted to smallInts, if possible.
  2224         "/ results are always converted to smallInts, if possible.
  2225 	"/ therefore, a largeInt in the smallInt range is not allowed (possible)
  2225         "/ therefore, a largeInt in the smallInt range is not allowed (possible)
  2226 	"/
  2226         "/
  2227 	aNumber class == SmallInteger ifTrue:[^ false ].
  2227         aNumber class == SmallInteger ifTrue:[^ false ].
  2228 	^ aNumber equalFromInteger:self
  2228         ^ aNumber equalFromInteger:self
  2229     ].
  2229     ].
  2230 
  2230 
  2231     (aNumber sign == sign) ifFalse:[^ false].
  2231     (aNumber sign == sign) ifFalse:[^ false].
  2232     ^ digitByteArray = aNumber digitBytes "/ ^ self absEq:aNumber
  2232     ^ digitByteArray = aNumber digitBytes "/ ^ self absEq:aNumber
  2233 
  2233 
  2238     "return true, if the argument, aNumber is less than the receiver"
  2238     "return true, if the argument, aNumber is less than the receiver"
  2239 
  2239 
  2240     |otherSign|
  2240     |otherSign|
  2241 
  2241 
  2242     (aNumber class == self class) ifFalse:[
  2242     (aNumber class == self class) ifFalse:[
  2243 	^ (aNumber < self)
  2243         ^ (aNumber < self)
  2244     ].
  2244     ].
  2245     otherSign := aNumber sign.
  2245     otherSign := aNumber sign.
  2246 
  2246 
  2247     (sign > 0) ifTrue:[
  2247     (sign > 0) ifTrue:[
  2248 	"I am positive"
  2248         "I am positive"
  2249 	(otherSign > 0) ifTrue:[^ aNumber absLess:self].
  2249         (otherSign > 0) ifTrue:[^ aNumber absLess:self].
  2250 	^ true "aNumber is <= 0"
  2250         ^ true "aNumber is <= 0"
  2251     ].
  2251     ].
  2252     (sign == 0) ifTrue:[
  2252     (sign == 0) ifTrue:[
  2253 	"I am zero"
  2253         "I am zero"
  2254 	(otherSign > 0) ifTrue:[^ false].
  2254         (otherSign > 0) ifTrue:[^ false].
  2255 	^ true
  2255         ^ true
  2256     ].
  2256     ].
  2257     "I am negative"
  2257     "I am negative"
  2258     (otherSign > 0) ifTrue:[^ false].
  2258     (otherSign > 0) ifTrue:[^ false].
  2259     (otherSign == 0) ifTrue:[^ false].
  2259     (otherSign == 0) ifTrue:[^ false].
  2260     ^ (self absLess:aNumber)
  2260     ^ (self absLess:aNumber)
  2269 
  2269 
  2270     h := self bitAnd:16r3FFFFFFF.
  2270     h := self bitAnd:16r3FFFFFFF.
  2271 
  2271 
  2272     l := digitByteArray size.
  2272     l := digitByteArray size.
  2273     l >= 8 ifTrue:[
  2273     l >= 8 ifTrue:[
  2274 	h := h bitXor:(digitByteArray at:l).
  2274         h := h bitXor:(digitByteArray at:l).
  2275 	h := h bitXor:((digitByteArray at:l-1) bitShift:8).
  2275         h := h bitXor:((digitByteArray at:l-1) bitShift:8).
  2276 	h := h bitXor:((digitByteArray at:l-2) bitShift:16).
  2276         h := h bitXor:((digitByteArray at:l-2) bitShift:16).
  2277 	h := h bitXor:((digitByteArray at:l-3) bitShift:22).
  2277         h := h bitXor:((digitByteArray at:l-3) bitShift:22).
  2278 	l >= 12 ifTrue:[
  2278         l >= 12 ifTrue:[
  2279 	    m := l // 2.
  2279             m := l // 2.
  2280 	    h := h bitXor:(digitByteArray at:m-1).
  2280             h := h bitXor:(digitByteArray at:m-1).
  2281 	    h := h bitXor:((digitByteArray at:m) bitShift:8).
  2281             h := h bitXor:((digitByteArray at:m) bitShift:8).
  2282 	    h := h bitXor:((digitByteArray at:m+1) bitShift:16).
  2282             h := h bitXor:((digitByteArray at:m+1) bitShift:16).
  2283 	    h := h bitXor:((digitByteArray at:m+2) bitShift:22).
  2283             h := h bitXor:((digitByteArray at:m+2) bitShift:22).
  2284 	].
  2284         ].
  2285 	^ h
  2285         ^ h
  2286     ].
  2286     ].
  2287     ^ (h bitShift:3) + l
  2287     ^ (h bitShift:3) + l
  2288 
  2288 
  2289     "
  2289     "
  2290      16r80000000 hash
  2290      16r80000000 hash
  2305 differenceFromInteger:anInteger
  2305 differenceFromInteger:anInteger
  2306     "sent, when anInteger does not know how to subtract the receiver.
  2306     "sent, when anInteger does not know how to subtract the receiver.
  2307      Return the result of 'anInteger - self'. The argument must be a SmallInteger."
  2307      Return the result of 'anInteger - self'. The argument must be a SmallInteger."
  2308 
  2308 
  2309     anInteger > 0 ifTrue:[
  2309     anInteger > 0 ifTrue:[
  2310 	sign > 0 ifTrue:[
  2310         sign > 0 ifTrue:[
  2311 	    ^ self absFastMinus:anInteger sign:-1
  2311             ^ self absFastMinus:anInteger sign:-1
  2312 	].
  2312         ].
  2313 	^ self absFastPlus:anInteger sign:1
  2313         ^ self absFastPlus:anInteger sign:1
  2314     ].
  2314     ].
  2315     anInteger == 0 ifTrue:[
  2315     anInteger == 0 ifTrue:[
  2316 	^ self negated
  2316         ^ self negated
  2317     ].
  2317     ].
  2318     sign > 0 ifTrue:[
  2318     sign > 0 ifTrue:[
  2319 	^ self absFastPlus:anInteger negated sign:-1
  2319         ^ self absFastPlus:anInteger negated sign:-1
  2320     ].
  2320     ].
  2321 
  2321 
  2322     self > anInteger ifTrue:[
  2322     self > anInteger ifTrue:[
  2323 	^ self absFastMinus:anInteger asLargeInteger sign:-1
  2323         ^ self absFastMinus:anInteger asLargeInteger sign:-1
  2324     ] ifFalse:[
  2324     ] ifFalse:[
  2325 	^ anInteger asLargeInteger absFastMinus:self sign:-1
  2325         ^ anInteger asLargeInteger absFastMinus:self sign:-1
  2326     ].
  2326     ].
  2327 
  2327 
  2328     "
  2328     "
  2329      12345678901234567890
  2329      12345678901234567890
  2330      -12345678901234567890
  2330      -12345678901234567890
  2346     "/ results are always converted to smallInts, if possible.
  2346     "/ results are always converted to smallInts, if possible.
  2347     "/ therefore, a largeInt in the smallInt range is not allowed (possible)
  2347     "/ therefore, a largeInt in the smallInt range is not allowed (possible)
  2348     "/
  2348     "/
  2349     anInteger class == SmallInteger ifTrue:[^ false ].
  2349     anInteger class == SmallInteger ifTrue:[^ false ].
  2350     anInteger class == self class ifFalse:[
  2350     anInteger class == self class ifFalse:[
  2351 	^ super equalFromInteger:anInteger
  2351         ^ super equalFromInteger:anInteger
  2352     ].
  2352     ].
  2353     (anInteger sign == sign) ifFalse:[^ false].
  2353     (anInteger sign == sign) ifFalse:[^ false].
  2354     ^ self absEq:anInteger
  2354     ^ self absEq:anInteger
  2355 !
  2355 !
  2356 
  2356 
  2758 sumFromInteger:anInteger
  2758 sumFromInteger:anInteger
  2759     "sent, when anInteger does not know how to add the receiver.
  2759     "sent, when anInteger does not know how to add the receiver.
  2760      Return the sum of the receiver and the argument, (which must be a SmallInteger)"
  2760      Return the sum of the receiver and the argument, (which must be a SmallInteger)"
  2761 
  2761 
  2762     anInteger > 0 ifTrue:[
  2762     anInteger > 0 ifTrue:[
  2763 	sign > 0 ifTrue:[
  2763         sign > 0 ifTrue:[
  2764 	    ^ self absFastPlus:anInteger sign:1
  2764             ^ self absFastPlus:anInteger sign:1
  2765 	].
  2765         ].
  2766 	^ self absFastMinus:anInteger sign:-1
  2766         ^ self absFastMinus:anInteger sign:-1
  2767     ].
  2767     ].
  2768     anInteger == 0 ifTrue:[
  2768     anInteger == 0 ifTrue:[
  2769 	^ self
  2769         ^ self
  2770     ].
  2770     ].
  2771     sign > 0 ifTrue:[
  2771     sign > 0 ifTrue:[
  2772 	^ self absFastMinus:anInteger sign:1
  2772         ^ self absFastMinus:anInteger sign:1
  2773     ].
  2773     ].
  2774     ^ self absFastPlus:anInteger sign:-1
  2774     ^ self absFastPlus:anInteger sign:-1
  2775 
  2775 
  2776 
  2776 
  2777     "
  2777     "
  2865             (dividend absSubtract: divisor) ifFalse:[ "result == 0"
  2865             (dividend absSubtract: divisor) ifFalse:[ "result == 0"
  2866                 ^ Array with:quo compressed with:0
  2866                 ^ Array with:quo compressed with:0
  2867             ].
  2867             ].
  2868         ].
  2868         ].
  2869         shift := shift - 1.
  2869         shift := shift - 1.
  2870         divisor div2.
  2870         divisor := divisor div2.
  2871     ].
  2871     ].
  2872     ^ Array with:quo compressed with:dividend compressed
  2872     ^ Array with:quo compressed with:dividend compressed
  2873 
  2873 
  2874     "
  2874     "
  2875      Time millisecondsToRun:[ 10000 timesRepeat:[  16000000000 absDivMod:4000000000] ]
  2875      Time millisecondsToRun:[ 10000 timesRepeat:[  16000000000 absDivMod:4000000000] ]
  2893      d2   "{ Class: SmallInteger }"
  2893      d2   "{ Class: SmallInteger }"
  2894      otherDigitByteArray |
  2894      otherDigitByteArray |
  2895 
  2895 
  2896 %{  /* NOCONTEXT */
  2896 %{  /* NOCONTEXT */
  2897     if (__isLargeInteger(aLargeInteger)) {
  2897     if (__isLargeInteger(aLargeInteger)) {
  2898 	OBJ _digitByteArray = __INST(digitByteArray);
  2898         OBJ _digitByteArray = __INST(digitByteArray);
  2899 	OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  2899         OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  2900 
  2900 
  2901 	if (__isByteArray(_digitByteArray)
  2901         if (__isByteArray(_digitByteArray)
  2902 	 && __isByteArray(_otherDigitByteArray)) {
  2902          && __isByteArray(_otherDigitByteArray)) {
  2903 	    INT _myLen = __byteArraySize(_digitByteArray);
  2903             INT _myLen = __byteArraySize(_digitByteArray);
  2904 	    INT _otherLen = __byteArraySize(_otherDigitByteArray);
  2904             INT _otherLen = __byteArraySize(_otherDigitByteArray);
  2905 
  2905 
  2906 	    unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  2906             unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  2907 	    unsigned char *_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  2907             unsigned char *_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  2908 
  2908 
  2909 	    if (_myLen == _otherLen) {
  2909             if (_myLen == _otherLen) {
  2910 tryAgain:
  2910 tryAgain:
  2911 		while (_myLen >= (sizeof(INT)*4)) {
  2911                 while (_myLen >= (sizeof(INT)*4)) {
  2912 		    if ( ((unsigned INT *)_myDigits)[0] != ((unsigned INT *)_otherDigits)[0]) {
  2912                     if ( ((unsigned INT *)_myDigits)[0] != ((unsigned INT *)_otherDigits)[0]) {
  2913 			RETURN(false);
  2913                         RETURN(false);
  2914 		    }
  2914                     }
  2915 		    if ( ((unsigned INT *)_myDigits)[1] != ((unsigned INT *)_otherDigits)[1]) {
  2915                     if ( ((unsigned INT *)_myDigits)[1] != ((unsigned INT *)_otherDigits)[1]) {
  2916 			RETURN(false);
  2916                         RETURN(false);
  2917 		    }
  2917                     }
  2918 		    if ( ((unsigned INT *)_myDigits)[2] != ((unsigned INT *)_otherDigits)[2]) {
  2918                     if ( ((unsigned INT *)_myDigits)[2] != ((unsigned INT *)_otherDigits)[2]) {
  2919 			RETURN(false);
  2919                         RETURN(false);
  2920 		    }
  2920                     }
  2921 		    if ( ((unsigned INT *)_myDigits)[3] != ((unsigned INT *)_otherDigits)[3]) {
  2921                     if ( ((unsigned INT *)_myDigits)[3] != ((unsigned INT *)_otherDigits)[3]) {
  2922 			RETURN(false);
  2922                         RETURN(false);
  2923 		    }
  2923                     }
  2924 		    _myDigits += sizeof(INT)*4;
  2924                     _myDigits += sizeof(INT)*4;
  2925 		    _otherDigits += sizeof(INT)*4;
  2925                     _otherDigits += sizeof(INT)*4;
  2926 		    _myLen -= sizeof(INT)*4;
  2926                     _myLen -= sizeof(INT)*4;
  2927 		}
  2927                 }
  2928 		while (_myLen >= (sizeof(INT))) {
  2928                 while (_myLen >= (sizeof(INT))) {
  2929 		    if ( *(unsigned INT *)_myDigits != *(unsigned INT *)_otherDigits) {
  2929                     if ( *(unsigned INT *)_myDigits != *(unsigned INT *)_otherDigits) {
  2930 			RETURN(false);
  2930                         RETURN(false);
  2931 		    }
  2931                     }
  2932 		    _myDigits += sizeof(INT);
  2932                     _myDigits += sizeof(INT);
  2933 		    _otherDigits += sizeof(INT);
  2933                     _otherDigits += sizeof(INT);
  2934 		    _myLen -= sizeof(INT);
  2934                     _myLen -= sizeof(INT);
  2935 		}
  2935                 }
  2936 		while (_myLen > 0) {
  2936                 while (_myLen > 0) {
  2937 		    if ( *_myDigits != *_otherDigits) {
  2937                     if ( *_myDigits != *_otherDigits) {
  2938 			RETURN(false);
  2938                         RETURN(false);
  2939 		    }
  2939                     }
  2940 		    _myDigits++;
  2940                     _myDigits++;
  2941 		    _otherDigits++;
  2941                     _otherDigits++;
  2942 		    _myLen--;
  2942                     _myLen--;
  2943 		}
  2943                 }
  2944 		RETURN(true);
  2944                 RETURN(true);
  2945 	    }
  2945             }
  2946 	    /* care for unnormalized ints */
  2946             /* care for unnormalized ints */
  2947 	    while ((_myLen > 0) && (_myDigits[_myLen-1] == 0)) _myLen--;
  2947             while ((_myLen > 0) && (_myDigits[_myLen-1] == 0)) _myLen--;
  2948 	    while ((_otherLen > 0) && (_otherDigits[_otherLen-1] == 0)) _otherLen--;
  2948             while ((_otherLen > 0) && (_otherDigits[_otherLen-1] == 0)) _otherLen--;
  2949 	    if (_myLen == _otherLen) goto tryAgain;
  2949             if (_myLen == _otherLen) goto tryAgain;
  2950 	    RETURN(false);
  2950             RETURN(false);
  2951 	}
  2951         }
  2952     }
  2952     }
  2953 %}.
  2953 %}.
  2954 
  2954 
  2955     len1 := digitByteArray size.
  2955     len1 := digitByteArray size.
  2956     otherDigitByteArray := aLargeInteger digitBytes.
  2956     otherDigitByteArray := aLargeInteger digitBytes.
  2960     "/ when properly normalized;
  2960     "/ when properly normalized;
  2961     "/ but we are tolerant here, to allow for unnormalized
  2961     "/ but we are tolerant here, to allow for unnormalized
  2962     "/ numbers to be compared ...
  2962     "/ numbers to be compared ...
  2963 
  2963 
  2964     [(digitByteArray basicAt:len1) == 0] whileTrue:[
  2964     [(digitByteArray basicAt:len1) == 0] whileTrue:[
  2965 	len1 := len1 - 1
  2965         len1 := len1 - 1
  2966     ].
  2966     ].
  2967     [(otherDigitByteArray basicAt:len2) == 0] whileTrue:[
  2967     [(otherDigitByteArray basicAt:len2) == 0] whileTrue:[
  2968 	len2 := len2 - 1
  2968         len2 := len2 - 1
  2969     ].
  2969     ].
  2970     (len1 ~~ len2) ifTrue:[^ false].
  2970     (len1 ~~ len2) ifTrue:[^ false].
  2971     [len1 > 0] whileTrue:[
  2971     [len1 > 0] whileTrue:[
  2972 	d1 := digitByteArray basicAt:len1.
  2972         d1 := digitByteArray basicAt:len1.
  2973 	d2 := otherDigitByteArray basicAt:len1.
  2973         d2 := otherDigitByteArray basicAt:len1.
  2974 	(d1 ~~ d2) ifTrue:[^ false].
  2974         (d1 ~~ d2) ifTrue:[^ false].
  2975 	len1 := len1 - 1
  2975         len1 := len1 - 1
  2976     ].
  2976     ].
  2977     ^ true
  2977     ^ true
  2978 
  2978 
  2979     "Modified: / 8.5.1999 / 18:37:02 / cg"
  2979     "Modified: / 8.5.1999 / 18:37:02 / cg"
  2980 !
  2980 !
  2989      count    "{ Class: SmallInteger }"
  2989      count    "{ Class: SmallInteger }"
  2990      newDigitByteArray result
  2990      newDigitByteArray result
  2991      ok|
  2991      ok|
  2992 
  2992 
  2993     aPositiveSmallInteger == 0 ifTrue:[
  2993     aPositiveSmallInteger == 0 ifTrue:[
  2994 	^ ZeroDivide raiseRequestWith:thisContext
  2994         ^ ZeroDivide raiseRequestWith:thisContext
  2995     ].
  2995     ].
  2996 
  2996 
  2997 "This cannot happen (if always normalized)
  2997 "This cannot happen (if always normalized)
  2998     self < aPositiveSmallInteger ifTrue:[
  2998     self < aPositiveSmallInteger ifTrue:[
  2999 	^ Array with:0 with:self
  2999         ^ Array with:0 with:self
  3000     ].
  3000     ].
  3001 "
  3001 "
  3002     count := digitByteArray size.
  3002     count := digitByteArray size.
  3003     result := self class basicNew numberOfDigits:count.
  3003     result := self class basicNew numberOfDigits:count.
  3004     newDigitByteArray := result digitBytes.
  3004     newDigitByteArray := result digitBytes.
  3009     __digits = __INST(digitByteArray);
  3009     __digits = __INST(digitByteArray);
  3010 
  3010 
  3011     if (__isByteArray(__digits)
  3011     if (__isByteArray(__digits)
  3012      && __isByteArray(newDigitByteArray)
  3012      && __isByteArray(newDigitByteArray)
  3013      && __bothSmallInteger(count, aPositiveSmallInteger)) {
  3013      && __bothSmallInteger(count, aPositiveSmallInteger)) {
  3014 	unsigned INT rest = 0;
  3014         unsigned INT rest = 0;
  3015 	int index = __intVal(count);
  3015         int index = __intVal(count);
  3016 	int index0;
  3016         int index0;
  3017 	unsigned INT divisor = __intVal(aPositiveSmallInteger);
  3017         unsigned INT divisor = __intVal(aPositiveSmallInteger);
  3018 	unsigned char *digitBytes = __ByteArrayInstPtr(__digits)->ba_element;
  3018         unsigned char *digitBytes = __ByteArrayInstPtr(__digits)->ba_element;
  3019 	unsigned char *resultBytes = __ByteArrayInstPtr(newDigitByteArray)->ba_element;
  3019         unsigned char *resultBytes = __ByteArrayInstPtr(newDigitByteArray)->ba_element;
  3020 
  3020 
  3021 	index0 = index - 1;
  3021         index0 = index - 1;
  3022 
  3022 
  3023 # if (__POINTER_SIZE__ == 8)
  3023 # if (__POINTER_SIZE__ == 8)
  3024 	if (sizeof(int) == 4) {
  3024         if (sizeof(int) == 4) {
  3025 	    /*
  3025             /*
  3026 	     * divide int-wise
  3026              * divide int-wise
  3027 	     */
  3027              */
  3028 	    if (divisor <= 0xFFFFFFFF) {
  3028             if (divisor <= 0xFFFFFFFF) {
  3029 		if ((index & 3) == 0) { /* even number of int32's */
  3029                 if ((index & 3) == 0) { /* even number of int32's */
  3030 		    while (index > 3) {
  3030                     while (index > 3) {
  3031 			unsigned INT t;
  3031                         unsigned INT t;
  3032 			unsigned INT div;
  3032                         unsigned INT div;
  3033 
  3033 
  3034 			index -= 4;
  3034                         index -= 4;
  3035 # if defined(__LSBFIRST__)
  3035 # if defined(__LSBFIRST__)
  3036 			t = *((unsigned int *)(&digitBytes[index]));
  3036                         t = *((unsigned int *)(&digitBytes[index]));
  3037 # else
  3037 # else
  3038 			t = digitBytes[index+3];
  3038                         t = digitBytes[index+3];
  3039 			t = (t << 8) | digitBytes[index+2];
  3039                         t = (t << 8) | digitBytes[index+2];
  3040 			t = (t << 8) | digitBytes[index+1];
  3040                         t = (t << 8) | digitBytes[index+1];
  3041 			t = (t << 8) | digitBytes[index];
  3041                         t = (t << 8) | digitBytes[index];
  3042 # endif
  3042 # endif
  3043 			t = t | (rest << 32);
  3043                         t = t | (rest << 32);
  3044 			div = t / divisor;
  3044                         div = t / divisor;
  3045 			rest = t % divisor;
  3045                         rest = t % divisor;
  3046 # if defined(__LSBFIRST__)
  3046 # if defined(__LSBFIRST__)
  3047 			*((unsigned int *)(&resultBytes[index])) = (div & 0xFFFFFFFF);
  3047                         *((unsigned int *)(&resultBytes[index])) = (div & 0xFFFFFFFF);
  3048 # else
  3048 # else
  3049 			resultBytes[index+3] = div >> 24;
  3049                         resultBytes[index+3] = div >> 24;
  3050 			resultBytes[index+2] = div >> 16;
  3050                         resultBytes[index+2] = div >> 16;
  3051 			resultBytes[index+1] = div >> 8;
  3051                         resultBytes[index+1] = div >> 8;
  3052 			resultBytes[index] = div /* & 0xFF */;
  3052                         resultBytes[index] = div /* & 0xFF */;
  3053 # endif
  3053 # endif
  3054 		    }
  3054                     }
  3055 		}
  3055                 }
  3056 	    }
  3056             }
  3057 	}
  3057         }
  3058 #endif
  3058 #endif
  3059 	/*
  3059         /*
  3060 	 * divide short-wise
  3060          * divide short-wise
  3061 	 */
  3061          */
  3062 	if (divisor <= 0xFFFF) {
  3062         if (divisor <= 0xFFFF) {
  3063 	    if ((index & 1) == 0) { /* even number of bytes */
  3063             if ((index & 1) == 0) { /* even number of bytes */
  3064 		while (index > 1) {
  3064                 while (index > 1) {
  3065 		    unsigned INT t;
  3065                     unsigned INT t;
  3066 		    unsigned INT div;
  3066                     unsigned INT div;
  3067 
  3067 
  3068 		    index -= 2;
  3068                     index -= 2;
  3069 #if defined(__LSBFIRST__)
  3069 #if defined(__LSBFIRST__)
  3070 		    t = *((unsigned short *)(&digitBytes[index]));
  3070                     t = *((unsigned short *)(&digitBytes[index]));
  3071 #else
  3071 #else
  3072 		    t = digitBytes[index+1];
  3072                     t = digitBytes[index+1];
  3073 		    t = (t << 8) | digitBytes[index];
  3073                     t = (t << 8) | digitBytes[index];
  3074 #endif
  3074 #endif
  3075 		    t = t | (rest << 16);
  3075                     t = t | (rest << 16);
  3076 		    div = t / divisor;
  3076                     div = t / divisor;
  3077 		    rest = t % divisor;
  3077                     rest = t % divisor;
  3078 #if defined(__LSBFIRST__)
  3078 #if defined(__LSBFIRST__)
  3079 		    *((unsigned short *)(&resultBytes[index])) = (div & 0xFFFF);
  3079                     *((unsigned short *)(&resultBytes[index])) = (div & 0xFFFF);
  3080 #else
  3080 #else
  3081 		    resultBytes[index+1] = div >> 8;
  3081                     resultBytes[index+1] = div >> 8;
  3082 		    resultBytes[index] = div /* & 0xFF */;
  3082                     resultBytes[index] = div /* & 0xFF */;
  3083 #endif
  3083 #endif
  3084 		}
  3084                 }
  3085 	    }
  3085             }
  3086 	}
  3086         }
  3087 	while (index > 0) {
  3087         while (index > 0) {
  3088 	    unsigned INT t;
  3088             unsigned INT t;
  3089 
  3089 
  3090 	    index--;
  3090             index--;
  3091 	    t = digitBytes[index];
  3091             t = digitBytes[index];
  3092 	    t = t | (rest << 8);
  3092             t = t | (rest << 8);
  3093 	    resultBytes[index] = t / divisor;
  3093             resultBytes[index] = t / divisor;
  3094 	    rest = t % divisor;
  3094             rest = t % divisor;
  3095 	}
  3095         }
  3096 	prevRest = __mkSmallInteger(rest);
  3096         prevRest = __mkSmallInteger(rest);
  3097 
  3097 
  3098 	/*
  3098         /*
  3099 	 * no need to normalize ?
  3099          * no need to normalize ?
  3100 	 */
  3100          */
  3101 	index = index0;
  3101         index = index0;
  3102 	while ((index >= sizeof(INT)) && (resultBytes[index]==0)) {
  3102         while ((index >= sizeof(INT)) && (resultBytes[index]==0)) {
  3103 	    index--;
  3103             index--;
  3104 	}
  3104         }
  3105 
  3105 
  3106 	if (index == index0) {
  3106         if (index == index0) {
  3107 	    if (index > sizeof(INT)) {
  3107             if (index > sizeof(INT)) {
  3108 		RETURN ( __ARRAY_WITH2(result, prevRest));
  3108                 RETURN ( __ARRAY_WITH2(result, prevRest));
  3109 	    }
  3109             }
  3110 	    if ((index == sizeof(INT))
  3110             if ((index == sizeof(INT))
  3111 	    && resultBytes[index0] >= 0x40) {
  3111             && resultBytes[index0] >= 0x40) {
  3112 		RETURN ( __ARRAY_WITH2(result, prevRest));
  3112                 RETURN ( __ARRAY_WITH2(result, prevRest));
  3113 	    }
  3113             }
  3114 	}
  3114         }
  3115 
  3115 
  3116 	/*
  3116         /*
  3117 	 * must compress
  3117          * must compress
  3118 	 */
  3118          */
  3119 	ok = true;
  3119         ok = true;
  3120     }
  3120     }
  3121 %}.
  3121 %}.
  3122     "
  3122     "
  3123      slow code - not normally reached
  3123      slow code - not normally reached
  3124      (could also do a primitiveFailure here)
  3124      (could also do a primitiveFailure here)
  3125     "
  3125     "
  3126     ok ifFalse:[
  3126     ok ifFalse:[
  3127 	^ self absDivMod:(self class value:aPositiveSmallInteger).
  3127         ^ self absDivMod:(self class value:aPositiveSmallInteger).
  3128     ].
  3128     ].
  3129 
  3129 
  3130     ^ Array with:(result compressed) with:prevRest
  3130     ^ Array with:(result compressed) with:prevRest
  3131 
  3131 
  3132     "
  3132     "
  3154     "/ the following code only works with
  3154     "/ the following code only works with
  3155     "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255
  3155     "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255
  3156 
  3156 
  3157     ((aSmallInteger < (SmallInteger minVal + 255))
  3157     ((aSmallInteger < (SmallInteger minVal + 255))
  3158     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
  3158     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
  3159 	^ self absMinus:(self class value:aSmallInteger) sign:newSign.
  3159         ^ self absMinus:(self class value:aSmallInteger) sign:newSign.
  3160     ].
  3160     ].
  3161 
  3161 
  3162     len := digitByteArray size.
  3162     len := digitByteArray size.
  3163 
  3163 
  3164     rsltLen := len "+ 1".
  3164     rsltLen := len "+ 1".
  3168     borrow := aSmallInteger abs.
  3168     borrow := aSmallInteger abs.
  3169 
  3169 
  3170 %{
  3170 %{
  3171     if (__isByteArray(__INST(digitByteArray))
  3171     if (__isByteArray(__INST(digitByteArray))
  3172      && __isByteArray(resultDigitByteArray)) {
  3172      && __isByteArray(resultDigitByteArray)) {
  3173 	unsigned INT __borrow = __intVal(borrow);
  3173         unsigned INT __borrow = __intVal(borrow);
  3174 	INT __diff;
  3174         INT __diff;
  3175 	int __index = 1;
  3175         int __index = 1;
  3176 	int __len = __intVal(len);
  3176         int __len = __intVal(len);
  3177 	unsigned char *__digitP = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3177         unsigned char *__digitP = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3178 	unsigned char *__resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  3178         unsigned char *__resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  3179 	int __len3;
  3179         int __len3;
  3180 
  3180 
  3181 #if defined(__LSBFIRST__)
  3181 #if defined(__LSBFIRST__)
  3182 # if (__POINTER_SIZE__ == 8)
  3182 # if (__POINTER_SIZE__ == 8)
  3183 	/*
  3183         /*
  3184 	 * subtract int-wise
  3184          * subtract int-wise
  3185 	 */
  3185          */
  3186 	__len3 = __len - 3;
  3186         __len3 = __len - 3;
  3187 	while (__index < __len3) {
  3187         while (__index < __len3) {
  3188 	    /* do not make this into one expression - ask cg why */
  3188             /* do not make this into one expression - ask cg why */
  3189 	    __diff = ((unsigned int *)(__digitP + __index-1))[0];
  3189             __diff = ((unsigned int *)(__digitP + __index-1))[0];
  3190 	    __diff -= (__borrow & 0xFFFFFFFFL);
  3190             __diff -= (__borrow & 0xFFFFFFFFL);
  3191 	    __borrow >>= 32;
  3191             __borrow >>= 32;
  3192 	    if (__diff < 0) {
  3192             if (__diff < 0) {
  3193 		/* __diff += 0x100000000; */
  3193                 /* __diff += 0x100000000; */
  3194 		__borrow++;
  3194                 __borrow++;
  3195 	    }
  3195             }
  3196 	    ((unsigned int *)(__resultP+__index-1))[0] = __diff;
  3196             ((unsigned int *)(__resultP+__index-1))[0] = __diff;
  3197 	    __index += 4;
  3197             __index += 4;
  3198 	}
  3198         }
  3199 # endif
  3199 # endif
  3200 	/*
  3200         /*
  3201 	 * subtract short-wise
  3201          * subtract short-wise
  3202 	 */
  3202          */
  3203 	while (__index < __len) {
  3203         while (__index < __len) {
  3204 	    /* do not make this into one expression - ask cg why */
  3204             /* do not make this into one expression - ask cg why */
  3205 	    __diff = ((unsigned short *)(__digitP+__index-1))[0];
  3205             __diff = ((unsigned short *)(__digitP+__index-1))[0];
  3206 	    __diff -= (__borrow & 0xFFFF);
  3206             __diff -= (__borrow & 0xFFFF);
  3207 	    __borrow >>= 16;
  3207             __borrow >>= 16;
  3208 	    if (__diff < 0) {
  3208             if (__diff < 0) {
  3209 		/* __diff += 0x10000; */
  3209                 /* __diff += 0x10000; */
  3210 		__borrow++;
  3210                 __borrow++;
  3211 	    } else {
  3211             } else {
  3212 		if (__borrow == 0) {
  3212                 if (__borrow == 0) {
  3213 		    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
  3213                     ((unsigned short *)(__resultP+__index-1))[0] = __diff;
  3214 		    __index += 2;
  3214                     __index += 2;
  3215 
  3215 
  3216 		    /* nothing more to subtract .. */
  3216                     /* nothing more to subtract .. */
  3217 		    while (__index < __len) {
  3217                     while (__index < __len) {
  3218 			((unsigned short *)(__resultP+__index-1))[0] = ((unsigned short *)(__digitP+__index-1))[0];
  3218                         ((unsigned short *)(__resultP+__index-1))[0] = ((unsigned short *)(__digitP+__index-1))[0];
  3219 			__index += 2;
  3219                         __index += 2;
  3220 		    }
  3220                     }
  3221 		    if (__index <= __len) {
  3221                     if (__index <= __len) {
  3222 			__resultP[__index-1] = __digitP[__index-1];
  3222                         __resultP[__index-1] = __digitP[__index-1];
  3223 		    }
  3223                     }
  3224 		    break;
  3224                     break;
  3225 		}
  3225                 }
  3226 	    }
  3226             }
  3227 	    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
  3227             ((unsigned short *)(__resultP+__index-1))[0] = __diff;
  3228 	    __index += 2;
  3228             __index += 2;
  3229 	}
  3229         }
  3230 #endif
  3230 #endif
  3231 	/*
  3231         /*
  3232 	 * subtract byte-wise
  3232          * subtract byte-wise
  3233 	 */
  3233          */
  3234 	while (__index <= __len) {
  3234         while (__index <= __len) {
  3235 	    __diff = __digitP[__index-1];
  3235             __diff = __digitP[__index-1];
  3236 	    __diff -= (__borrow & 0xFF);
  3236             __diff -= (__borrow & 0xFF);
  3237 	    __borrow >>= 8;
  3237             __borrow >>= 8;
  3238 	    if (__diff < 0) {
  3238             if (__diff < 0) {
  3239 		/* __diff += 0x100; */
  3239                 /* __diff += 0x100; */
  3240 		__borrow++;
  3240                 __borrow++;
  3241 	    } else {
  3241             } else {
  3242 		if (__borrow == 0) {
  3242                 if (__borrow == 0) {
  3243 		    __resultP[__index-1] = __diff;
  3243                     __resultP[__index-1] = __diff;
  3244 		    __index++;
  3244                     __index++;
  3245 
  3245 
  3246 		    /* nothing more to subtract .. */
  3246                     /* nothing more to subtract .. */
  3247 		    while (__index <= __len) {
  3247                     while (__index <= __len) {
  3248 			__resultP[__index-1] = __digitP[__index-1];
  3248                         __resultP[__index-1] = __digitP[__index-1];
  3249 			__index++;
  3249                         __index++;
  3250 		    }
  3250                     }
  3251 		    break;
  3251                     break;
  3252 		}
  3252                 }
  3253 	    }
  3253             }
  3254 	    __resultP[__index-1] = __diff;
  3254             __resultP[__index-1] = __diff;
  3255 	    __index++;
  3255             __index++;
  3256 	}
  3256         }
  3257 	lastDigit = __mkSmallInteger( __resultP[__index-1-1] );
  3257         lastDigit = __mkSmallInteger( __resultP[__index-1-1] );
  3258 	ok = true;
  3258         ok = true;
  3259     }
  3259     }
  3260 %}.
  3260 %}.
  3261 
  3261 
  3262     ok == true ifFalse:[        "/ cannot happen
  3262     ok == true ifFalse:[        "/ cannot happen
  3263 	index := 1.
  3263         index := 1.
  3264 	[borrow ~~ 0] whileTrue:[
  3264         [borrow ~~ 0] whileTrue:[
  3265 	    (index <= len) ifTrue:[
  3265             (index <= len) ifTrue:[
  3266 		diff := (digitByteArray basicAt:index) - (borrow bitAnd:16rFF).
  3266                 diff := (digitByteArray basicAt:index) - (borrow bitAnd:16rFF).
  3267 		borrow := borrow bitShift:-8.
  3267                 borrow := borrow bitShift:-8.
  3268 		diff < 0 ifTrue:[
  3268                 diff < 0 ifTrue:[
  3269 		    diff := diff + 256.
  3269                     diff := diff + 256.
  3270 		    borrow := borrow + 1.
  3270                     borrow := borrow + 1.
  3271 		]
  3271                 ]
  3272 	    ] ifFalse:[
  3272             ] ifFalse:[
  3273 		diff := borrow bitAnd:255.
  3273                 diff := borrow bitAnd:255.
  3274 		borrow := borrow bitShift:-8.
  3274                 borrow := borrow bitShift:-8.
  3275 	    ].
  3275             ].
  3276 	    resultDigitByteArray basicAt:index put:(lastDigit := diff).
  3276             resultDigitByteArray basicAt:index put:(lastDigit := diff).
  3277 	    index := index + 1
  3277             index := index + 1
  3278 	].
  3278         ].
  3279 	[index <= len] whileTrue:[
  3279         [index <= len] whileTrue:[
  3280 	    resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
  3280             resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
  3281 	    index := index + 1
  3281             index := index + 1
  3282 	].
  3282         ].
  3283 	(index <= rsltLen) ifTrue:[
  3283         (index <= rsltLen) ifTrue:[
  3284 	    lastDigit := 0.
  3284             lastDigit := 0.
  3285 	]
  3285         ]
  3286     ].
  3286     ].
  3287 
  3287 
  3288     (lastDigit == 0 or:[rsltLen <= SmallInteger maxBytes]) ifTrue:[
  3288     (lastDigit == 0 or:[rsltLen <= SmallInteger maxBytes]) ifTrue:[
  3289 	^ result compressed.
  3289         ^ result compressed.
  3290     ].
  3290     ].
  3291     ^ result
  3291     ^ result
  3292 
  3292 
  3293     "
  3293     "
  3294      12345678900000000000 absFastMinus:1 sign:1
  3294      12345678900000000000 absFastMinus:1 sign:1
  3319     "/ the following code only works with
  3319     "/ the following code only works with
  3320     "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255
  3320     "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255
  3321 
  3321 
  3322     ((aSmallInteger < (SmallInteger minVal + 255))
  3322     ((aSmallInteger < (SmallInteger minVal + 255))
  3323     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
  3323     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
  3324 	^ self absPlus:(self class value:aSmallInteger) sign:newSign.
  3324         ^ self absPlus:(self class value:aSmallInteger) sign:newSign.
  3325     ].
  3325     ].
  3326 
  3326 
  3327     len := rsltLen := digitByteArray size.
  3327     len := rsltLen := digitByteArray size.
  3328     "/
  3328     "/
  3329     "/ there can only be an overflow from the high byte,
  3329     "/ there can only be an overflow from the high byte,
  3330     "/ if it is 255 (since the other number is definitely smaller)
  3330     "/ if it is 255 (since the other number is definitely smaller)
  3331     "/
  3331     "/
  3332     (digitByteArray at:len) == 16rFF ifTrue:[
  3332     (digitByteArray at:len) == 16rFF ifTrue:[
  3333 	rsltLen := len + 1.
  3333         rsltLen := len + 1.
  3334     ] ifFalse:[
  3334     ] ifFalse:[
  3335 	"/ or the argument has something in the high byte ..
  3335         "/ or the argument has something in the high byte ..
  3336 %{
  3336 %{
  3337 #if __POINTER_SIZE__ == 8
  3337 #if __POINTER_SIZE__ == 8
  3338 	if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
  3338         if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
  3339 	    rsltLen = __mkSmallInteger(__intVal(len) + 1);
  3339             rsltLen = __mkSmallInteger(__intVal(len) + 1);
  3340 	}
  3340         }
  3341 #else
  3341 #else
  3342 	if (__intVal(aSmallInteger) & 0xFF000000) {
  3342         if (__intVal(aSmallInteger) & 0xFF000000) {
  3343 	    rsltLen = __mkSmallInteger(__intVal(len) + 1);
  3343             rsltLen = __mkSmallInteger(__intVal(len) + 1);
  3344 	}
  3344         }
  3345 #endif
  3345 #endif
  3346 %}
  3346 %}
  3347     ].
  3347     ].
  3348 
  3348 
  3349     result := self class basicNew numberOfDigits:rsltLen sign:newSign.
  3349     result := self class basicNew numberOfDigits:rsltLen sign:newSign.
  3351 
  3351 
  3352 %{
  3352 %{
  3353     if (__isByteArray(__INST(digitByteArray))
  3353     if (__isByteArray(__INST(digitByteArray))
  3354      && __isByteArray(resultDigitByteArray)
  3354      && __isByteArray(resultDigitByteArray)
  3355      && __isSmallInteger(aSmallInteger)) {
  3355      && __isSmallInteger(aSmallInteger)) {
  3356 	/* carry is NOT unsigned (see negation below) */
  3356         /* carry is NOT unsigned (see negation below) */
  3357 	INT __carry = __intVal(aSmallInteger);
  3357         INT __carry = __intVal(aSmallInteger);
  3358 	int __index = 1;
  3358         int __index = 1;
  3359 	int __len = __intVal(len);
  3359         int __len = __intVal(len);
  3360 	unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
  3360         unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
  3361 	unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
  3361         unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
  3362 	INT __ptrDelta = __dst - __src;
  3362         INT __ptrDelta = __dst - __src;
  3363 	unsigned char *__srcLast = __src + __len - 1;
  3363         unsigned char *__srcLast = __src + __len - 1;
  3364 	int __rsltLen = __intVal(rsltLen);
  3364         int __rsltLen = __intVal(rsltLen);
  3365 
  3365 
  3366 	if (__carry < 0) {
  3366         if (__carry < 0) {
  3367 	    __carry = -__carry;
  3367             __carry = -__carry;
  3368 	}
  3368         }
  3369 
  3369 
  3370 #if defined(__LSBFIRST__)
  3370 #if defined(__LSBFIRST__)
  3371 # if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
  3371 # if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
  3372 #  if 0 /* NOTICE - the code below is 20% slower ... - why */
  3372 #  if 0 /* NOTICE - the code below is 20% slower ... - why */
  3373 	/*
  3373         /*
  3374 	 * add long-wise
  3374          * add long-wise
  3375 	 */
  3375          */
  3376 	asm("  jecxz nothingToDo                                      \n\
  3376         asm("  jecxz nothingToDo                                      \n\
  3377 	       movl  %%eax, %%esi      /* __src input */              \n\
  3377                movl  %%eax, %%esi      /* __src input */              \n\
  3378 	       movl  %%ebx, %%edi      /* __dst input */              \n\
  3378                movl  %%ebx, %%edi      /* __dst input */              \n\
  3379 								      \n\
  3379                                                                       \n\
  3380 	       /* the first 4-byte int */                             \n\
  3380                /* the first 4-byte int */                             \n\
  3381 	       lodsl                   /* fetch */                    \n\
  3381                lodsl                   /* fetch */                    \n\
  3382 	       addl  %%edx, %%eax      /* add */                      \n\
  3382                addl  %%edx, %%eax      /* add */                      \n\
  3383 	       stosl                   /* store */                    \n\
  3383                stosl                   /* store */                    \n\
  3384 	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
  3384                leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
  3385 	       jecxz doneLoop          /* any more ? */               \n\
  3385                jecxz doneLoop          /* any more ? */               \n\
  3386 	       /* remaining 4-byte ints */                            \n\
  3386                /* remaining 4-byte ints */                            \n\
  3387 	       jmp   addLoop                                          \n\
  3387                jmp   addLoop                                          \n\
  3388 								      \n\
  3388                                                                       \n\
  3389 	       .align 8                                               \n\
  3389                .align 8                                               \n\
  3390 	     addLoop:                                                 \n\
  3390              addLoop:                                                 \n\
  3391 	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
  3391                movl  0(%%esi), %%ebx   /* fetch  */                   \n\
  3392 	       jnc   copyLoop2                                        \n\
  3392                jnc   copyLoop2                                        \n\
  3393 	       movl  $0, %%eax                                        \n\
  3393                movl  $0, %%eax                                        \n\
  3394 	       leal  4(%%esi), %%esi                                  \n\
  3394                leal  4(%%esi), %%esi                                  \n\
  3395 	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
  3395                adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
  3396 	       leal  8(%%edi), %%edi                                  \n\
  3396                leal  8(%%edi), %%edi                                  \n\
  3397 	       movl  %%eax, -8(%%edi)  /* store */                    \n\
  3397                movl  %%eax, -8(%%edi)  /* store */                    \n\
  3398 	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
  3398                leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
  3399 	       jecxz doneLoop          /* any more ? */               \n\
  3399                jecxz doneLoop          /* any more ? */               \n\
  3400 								      \n\
  3400                                                                       \n\
  3401 	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
  3401                movl  0(%%esi), %%ebx   /* fetch  */                   \n\
  3402 	       movl  $0, %%eax                                        \n\
  3402                movl  $0, %%eax                                        \n\
  3403 	       leal  4(%%esi), %%esi                                  \
  3403                leal  4(%%esi), %%esi                                  \
  3404 	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
  3404                adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
  3405 	       movl  %%eax, -4(%%edi)  /* store */                    \n\
  3405                movl  %%eax, -4(%%edi)  /* store */                    \n\
  3406 								      \n\
  3406                                                                       \n\
  3407 	       loop  addLoop                                          \n\
  3407                loop  addLoop                                          \n\
  3408 	       jmp   doneLoop                                         \n\
  3408                jmp   doneLoop                                         \n\
  3409 								      \n\
  3409                                                                       \n\
  3410 	       .align 8                                               \n\
  3410                .align 8                                               \n\
  3411 	     copyLoop:                                                \n\
  3411              copyLoop:                                                \n\
  3412 	       movl  0(%%esi), %%ebx                                  \n\
  3412                movl  0(%%esi), %%ebx                                  \n\
  3413 	     copyLoop2:                                               \n\
  3413              copyLoop2:                                               \n\
  3414 	       add   $4, %%esi                                        \n\
  3414                add   $4, %%esi                                        \n\
  3415 	       add   $4, %%edi                                        \n\
  3415                add   $4, %%edi                                        \n\
  3416 	       movl  %%ebx, -4(%%edi)                                 \n\
  3416                movl  %%ebx, -4(%%edi)                                 \n\
  3417 	       loop  copyLoop                                         \n\
  3417                loop  copyLoop                                         \n\
  3418 								      \n\
  3418                                                                       \n\
  3419 	     doneLoop:                                                \n\
  3419              doneLoop:                                                \n\
  3420 	       movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
  3420                movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
  3421 	       adcl  $0, %%edx                                        \n\
  3421                adcl  $0, %%edx                                        \n\
  3422 	       movl  %%esi, %%eax      /* __src output */             \n\
  3422                movl  %%esi, %%eax      /* __src output */             \n\
  3423 	     nothingToDo:                                             \n\
  3423              nothingToDo:                                             \n\
  3424 	    " : "=d"  ((unsigned long)(__carry)),
  3424             " : "=d"  ((unsigned long)(__carry)),
  3425 		"=a"  (__src)
  3425                 "=a"  (__src)
  3426 	      : "1"   (__src),
  3426               : "1"   (__src),
  3427 		"b"   (__dst),
  3427                 "b"   (__dst),
  3428 		"c"   (__len / 4),
  3428                 "c"   (__len / 4),
  3429 		"0"   (__carry)
  3429                 "0"   (__carry)
  3430 	      : "esi", "edi");
  3430               : "esi", "edi");
  3431 
  3431 
  3432 #  else
  3432 #  else
  3433 	{
  3433         {
  3434 	    unsigned char *__srcLastX;
  3434             unsigned char *__srcLastX;
  3435 
  3435 
  3436 	    __srcLastX = __srcLast - 3 - 4;
  3436             __srcLastX = __srcLast - 3 - 4;
  3437 	    while (__src <= __srcLastX) {
  3437             while (__src <= __srcLastX) {
  3438 		unsigned int __sum, __sum2;
  3438                 unsigned int __sum, __sum2;
  3439 		unsigned __digit1, __digit2;
  3439                 unsigned __digit1, __digit2;
  3440 
  3440 
  3441 		__digit1 = ((unsigned *)__src)[0];
  3441                 __digit1 = ((unsigned *)__src)[0];
  3442 		__digit2 = ((unsigned *)__src)[1];
  3442                 __digit2 = ((unsigned *)__src)[1];
  3443 		asm ("addl %%edx,%%ecx          \n\
  3443                 asm ("addl %%edx,%%ecx          \n\
  3444 		      adcl $0, %%eax            \n\
  3444                       adcl $0, %%eax            \n\
  3445 		      movl $0, %%edx            \n\
  3445                       movl $0, %%edx            \n\
  3446 		      adcl $0, %%edx"
  3446                       adcl $0, %%edx"
  3447 			: "=d"  ((unsigned long)(__carry)),
  3447                         : "=d"  ((unsigned long)(__carry)),
  3448 			  "=c"  ((unsigned long)(__sum)),
  3448                           "=c"  ((unsigned long)(__sum)),
  3449 			  "=a"  ((unsigned long)(__sum2))
  3449                           "=a"  ((unsigned long)(__sum2))
  3450 			: "0"   ((unsigned long)(__carry)),
  3450                         : "0"   ((unsigned long)(__carry)),
  3451 			  "1"   (__digit1),
  3451                           "1"   (__digit1),
  3452 			  "2"   (__digit2));
  3452                           "2"   (__digit2));
  3453 
  3453 
  3454 		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3454                 ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3455 		((unsigned int *)(__src + __ptrDelta))[1] = __sum2;
  3455                 ((unsigned int *)(__src + __ptrDelta))[1] = __sum2;
  3456 
  3456 
  3457 		__src += 8;
  3457                 __src += 8;
  3458 
  3458 
  3459 		if (__carry == 0) {
  3459                 if (__carry == 0) {
  3460 		    while (__src <= __srcLastX) {
  3460                     while (__src <= __srcLastX) {
  3461 			/* copy over words */
  3461                         /* copy over words */
  3462 			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3462                         ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3463 			((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
  3463                         ((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
  3464 			__src += 8;
  3464                         __src += 8;
  3465 		    }
  3465                     }
  3466 		    while (__src <= __srcLast) {
  3466                     while (__src <= __srcLast) {
  3467 			/* copy over bytes */
  3467                         /* copy over bytes */
  3468 			__src[__ptrDelta] = __src[0];
  3468                         __src[__ptrDelta] = __src[0];
  3469 			__src ++;
  3469                         __src ++;
  3470 		    }
  3470                     }
  3471 		    goto doneSource;
  3471                     goto doneSource;
  3472 		}
  3472                 }
  3473 	    }
  3473             }
  3474 
  3474 
  3475 	    __srcLastX = __srcLastX + 4;
  3475             __srcLastX = __srcLastX + 4;
  3476 	    if (__src <= __srcLastX) {
  3476             if (__src <= __srcLastX) {
  3477 		unsigned int __sum, __digit;
  3477                 unsigned int __sum, __digit;
  3478 
  3478 
  3479 		__digit = ((unsigned *)__src)[0];
  3479                 __digit = ((unsigned *)__src)[0];
  3480 
  3480 
  3481 		asm ("addl %%eax,%%edx  \n\
  3481                 asm ("addl %%eax,%%edx  \n\
  3482 		      movl $0,%%eax     \n\
  3482                       movl $0,%%eax     \n\
  3483 		      adcl $0,%%eax"
  3483                       adcl $0,%%eax"
  3484 			: "=a"  ((unsigned long)(__carry)),
  3484                         : "=a"  ((unsigned long)(__carry)),
  3485 			  "=d"  ((unsigned long)(__sum))
  3485                           "=d"  ((unsigned long)(__sum))
  3486 			: "0"   ((unsigned long)(__carry)),
  3486                         : "0"   ((unsigned long)(__carry)),
  3487 			  "1"   (__digit) );
  3487                           "1"   (__digit) );
  3488 
  3488 
  3489 		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3489                 ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3490 		__src += 4;
  3490                 __src += 4;
  3491 
  3491 
  3492 		if (__carry == 0) {
  3492                 if (__carry == 0) {
  3493 		    while (__src <= __srcLast) {
  3493                     while (__src <= __srcLast) {
  3494 			/* copy over bytes */
  3494                         /* copy over bytes */
  3495 			__src[__ptrDelta] = __src[0];
  3495                         __src[__ptrDelta] = __src[0];
  3496 			__src ++;
  3496                         __src ++;
  3497 		    }
  3497                     }
  3498 		    goto doneSource;
  3498                     goto doneSource;
  3499 		}
  3499                 }
  3500 	    }
  3500             }
  3501 	}
  3501         }
  3502 #  endif
  3502 #  endif
  3503 # else /* not i386-GNUC */
  3503 # else /* not i386-GNUC */
  3504 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  3504 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  3505 	{
  3505         {
  3506 	    unsigned char *__srcLast4;
  3506             unsigned char *__srcLast4;
  3507 
  3507 
  3508 	    /*
  3508             /*
  3509 	     * add long-wise
  3509              * add long-wise
  3510 	     */
  3510              */
  3511 	    __srcLast4 = __srcLast - 3;
  3511             __srcLast4 = __srcLast - 3;
  3512 	    while (__src <= __srcLast4) {
  3512             while (__src <= __srcLast4) {
  3513 		unsigned int __sum;
  3513                 unsigned int __sum;
  3514 
  3514 
  3515 		__sum = ((unsigned int *)__src)[0];
  3515                 __sum = ((unsigned int *)__src)[0];
  3516 		asm {
  3516                 asm {
  3517 		      mov eax, __sum
  3517                       mov eax, __sum
  3518 		      add eax, __carry
  3518                       add eax, __carry
  3519 		      mov edx, 0
  3519                       mov edx, 0
  3520 		      adc edx, 0
  3520                       adc edx, 0
  3521 		      mov __sum, eax
  3521                       mov __sum, eax
  3522 		      mov __carry, edx
  3522                       mov __carry, edx
  3523 		    }
  3523                     }
  3524 
  3524 
  3525 		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3525                 ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3526 		__src += 4;
  3526                 __src += 4;
  3527 		if (__carry == 0) {
  3527                 if (__carry == 0) {
  3528 		    while (__src <= __srcLast4) {
  3528                     while (__src <= __srcLast4) {
  3529 			/* copy over words */
  3529                         /* copy over words */
  3530 			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3530                         ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3531 			__src += 4;
  3531                         __src += 4;
  3532 		    }
  3532                     }
  3533 		    while (__src <= __srcLast) {
  3533                     while (__src <= __srcLast) {
  3534 			/* copy over bytes */
  3534                         /* copy over bytes */
  3535 			__src[__ptrDelta] = __src[0];
  3535                         __src[__ptrDelta] = __src[0];
  3536 			__src ++;
  3536                         __src ++;
  3537 		    }
  3537                     }
  3538 		    goto doneSource;
  3538                     goto doneSource;
  3539 		}
  3539                 }
  3540 	    }
  3540             }
  3541 	}
  3541         }
  3542 #  else /* not i386-WIN32 */
  3542 #  else /* not i386-WIN32 */
  3543 #   if defined(__LSBFIRST__) && (__POINTER_SIZE__ == 8)
  3543 #   if defined(__LSBFIRST__) && (__POINTER_SIZE__ == 8)
  3544 	{
  3544         {
  3545 	    unsigned char *__srcLast4;
  3545             unsigned char *__srcLast4;
  3546 
  3546 
  3547 	    /*
  3547             /*
  3548 	     * add long-wise
  3548              * add long-wise
  3549 	     */
  3549              */
  3550 	    __srcLast4 = __srcLast - 3;
  3550             __srcLast4 = __srcLast - 3;
  3551 	    while (__src <= __srcLast4) {
  3551             while (__src <= __srcLast4) {
  3552 		unsigned INT __sum;
  3552                 unsigned INT __sum;
  3553 
  3553 
  3554 		__sum = ((unsigned int *)__src)[0] + __carry;
  3554                 __sum = ((unsigned int *)__src)[0] + __carry;
  3555 		((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
  3555                 ((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
  3556 		__src += 4;
  3556                 __src += 4;
  3557 		__carry = __sum >> 32;
  3557                 __carry = __sum >> 32;
  3558 		if (__carry == 0) {
  3558                 if (__carry == 0) {
  3559 		    while (__src <= __srcLast4) {
  3559                     while (__src <= __srcLast4) {
  3560 			/* copy over words */
  3560                         /* copy over words */
  3561 			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3561                         ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3562 			__src += 4;
  3562                         __src += 4;
  3563 		    }
  3563                     }
  3564 		    while (__src <= __srcLast) {
  3564                     while (__src <= __srcLast) {
  3565 			/* copy over bytes */
  3565                         /* copy over bytes */
  3566 			__src[__ptrDelta] = __src[0];
  3566                         __src[__ptrDelta] = __src[0];
  3567 			__src ++;
  3567                         __src ++;
  3568 		    }
  3568                     }
  3569 		    goto doneSource;
  3569                     goto doneSource;
  3570 		}
  3570                 }
  3571 	    }
  3571             }
  3572 	}
  3572         }
  3573 #   endif /* LSB+64bit */
  3573 #   endif /* LSB+64bit */
  3574 #  endif /* __i386__ & WIN32 */
  3574 #  endif /* __i386__ & WIN32 */
  3575 # endif /* __i386__ & GNUC */
  3575 # endif /* __i386__ & GNUC */
  3576 
  3576 
  3577 	/*
  3577         /*
  3578 	 * add short-wise
  3578          * add short-wise
  3579 	 */
  3579          */
  3580 	while (__src < __srcLast) {
  3580         while (__src < __srcLast) {
  3581 	    __carry += ((unsigned short *)__src)[0];
  3581             __carry += ((unsigned short *)__src)[0];
  3582 	    ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
  3582             ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
  3583 	    __carry >>= 16;
  3583             __carry >>= 16;
  3584 	    __src += 2;
  3584             __src += 2;
  3585 	}
  3585         }
  3586 	/*
  3586         /*
  3587 	 * last (odd) byte
  3587          * last (odd) byte
  3588 	 */
  3588          */
  3589 	if (__src <= __srcLast) {
  3589         if (__src <= __srcLast) {
  3590 	    __carry += __src[0];
  3590             __carry += __src[0];
  3591 	    __src[__ptrDelta] = __carry /* & 0xFF */;
  3591             __src[__ptrDelta] = __carry /* & 0xFF */;
  3592 	    __carry >>= 8;
  3592             __carry >>= 8;
  3593 	    __src++;
  3593             __src++;
  3594 	}
  3594         }
  3595 #else /* not __LSBFIRST__ */
  3595 #else /* not __LSBFIRST__ */
  3596 
  3596 
  3597 	/*
  3597         /*
  3598 	 * add byte-wise
  3598          * add byte-wise
  3599 	 */
  3599          */
  3600 	while (__src <= __srcLast) {
  3600         while (__src <= __srcLast) {
  3601 	    __carry += __src[0];
  3601             __carry += __src[0];
  3602 	    __src[__ptrDelta] = __carry /* & 0xFF */;
  3602             __src[__ptrDelta] = __carry /* & 0xFF */;
  3603 	    __src++;
  3603             __src++;
  3604 	    __carry >>= 8;
  3604             __carry >>= 8;
  3605 
  3605 
  3606 	    if (__carry == 0) {
  3606             if (__carry == 0) {
  3607 		while (__src <= __srcLast) {
  3607                 while (__src <= __srcLast) {
  3608 		    /* copy over rest */
  3608                     /* copy over rest */
  3609 		    __src[__ptrDelta] = __src[0];
  3609                     __src[__ptrDelta] = __src[0];
  3610 		    __src++;
  3610                     __src++;
  3611 		}
  3611                 }
  3612 		goto doneSource;
  3612                 goto doneSource;
  3613 	    }
  3613             }
  3614 	}
  3614         }
  3615 #endif /* __LSBFIRST__ */
  3615 #endif /* __LSBFIRST__ */
  3616 
  3616 
  3617     doneSource: ;
  3617     doneSource: ;
  3618 	/*
  3618         /*
  3619 	 * now, at most one other byte is to be stored ...
  3619          * now, at most one other byte is to be stored ...
  3620 	 */
  3620          */
  3621 	if (__len < __rsltLen) {
  3621         if (__len < __rsltLen) {
  3622 	    __src[__ptrDelta] = __carry /* & 0xFF */;
  3622             __src[__ptrDelta] = __carry /* & 0xFF */;
  3623 	    __src++;
  3623             __src++;
  3624 	}
  3624         }
  3625 
  3625 
  3626 	if (__src[__ptrDelta-1]) {      /* lastDigit */
  3626         if (__src[__ptrDelta-1]) {      /* lastDigit */
  3627 	    RETURN (result);
  3627             RETURN (result);
  3628 	}
  3628         }
  3629 	ok = true;
  3629         ok = true;
  3630     }
  3630     }
  3631 %}.
  3631 %}.
  3632 
  3632 
  3633     ok ~~ true ifTrue:[
  3633     ok ~~ true ifTrue:[
  3634 	index := 1.
  3634         index := 1.
  3635 	carry := aSmallInteger abs.
  3635         carry := aSmallInteger abs.
  3636 
  3636 
  3637 	[carry ~~ 0] whileTrue:[
  3637         [carry ~~ 0] whileTrue:[
  3638 	    (index <= len) ifTrue:[
  3638             (index <= len) ifTrue:[
  3639 		carry := (digitByteArray basicAt:index) + carry.
  3639                 carry := (digitByteArray basicAt:index) + carry.
  3640 	    ].
  3640             ].
  3641 	    resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
  3641             resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
  3642 	    carry := carry bitShift:-8.
  3642             carry := carry bitShift:-8.
  3643 	    index := index + 1
  3643             index := index + 1
  3644 	].
  3644         ].
  3645 
  3645 
  3646 	(index <= rsltLen) ifTrue:[
  3646         (index <= rsltLen) ifTrue:[
  3647 	    [index <= len] whileTrue:[
  3647             [index <= len] whileTrue:[
  3648 		resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
  3648                 resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
  3649 		index := index + 1
  3649                 index := index + 1
  3650 	    ].
  3650             ].
  3651 	    lastDigit := 0.
  3651             lastDigit := 0.
  3652 	].
  3652         ].
  3653 
  3653 
  3654 	(lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
  3654         (lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
  3655 	    ^ result
  3655             ^ result
  3656 	].
  3656         ].
  3657     ].
  3657     ].
  3658 
  3658 
  3659     ^ result compressed
  3659     ^ result compressed
  3660 
  3660 
  3661     "Modified: 24.3.1997 / 21:32:41 / cg"
  3661     "Modified: 24.3.1997 / 21:32:41 / cg"
  3797 
  3797 
  3798 %{  /* NOCONTEXT */
  3798 %{  /* NOCONTEXT */
  3799 #if defined(__LSBFIRST__)
  3799 #if defined(__LSBFIRST__)
  3800     if (__isByteArray(__INST(digitByteArray))
  3800     if (__isByteArray(__INST(digitByteArray))
  3801      && __isLargeInteger(aLargeInteger)) {
  3801      && __isLargeInteger(aLargeInteger)) {
  3802 	OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  3802         OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  3803 
  3803 
  3804 	if (__isByteArray(_otherDigitByteArray)) {
  3804         if (__isByteArray(_otherDigitByteArray)) {
  3805 	    unsigned char *_myDigits = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3805             unsigned char *_myDigits = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3806 	    unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  3806             unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  3807 	    INT _myLen = __byteArraySize(__INST(digitByteArray));
  3807             INT _myLen = __byteArraySize(__INST(digitByteArray));
  3808 
  3808 
  3809 	    if (_myLen == __POINTER_SIZE__) {
  3809             if (_myLen == __POINTER_SIZE__) {
  3810 		INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3810                 INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3811 
  3811 
  3812 		if (_otherLen == __POINTER_SIZE__) {
  3812                 if (_otherLen == __POINTER_SIZE__) {
  3813 		    unsigned INT _myVal = *((unsigned INT *)_myDigits);
  3813                     unsigned INT _myVal = *((unsigned INT *)_myDigits);
  3814 		    unsigned INT _otherVal = *((unsigned INT *)_otherDigits);
  3814                     unsigned INT _otherVal = *((unsigned INT *)_otherDigits);
  3815 		    RETURN( (_myVal <= _otherVal) ? true : false );
  3815                     RETURN( (_myVal <= _otherVal) ? true : false );
  3816 		}
  3816                 }
  3817 	    }
  3817             }
  3818 # if defined(UINT64) && (__POINTER_SIZE__ != 8)
  3818 # if defined(UINT64) && (__POINTER_SIZE__ != 8)
  3819 	    if (_myLen == __POINTER_SIZE__) {
  3819             if (_myLen == __POINTER_SIZE__) {
  3820 		INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3820                 INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3821 
  3821 
  3822 		if (_otherLen <= 8) {
  3822                 if (_otherLen <= 8) {
  3823 		    UINT64 _myVal = (UINT64)(*((UINT *)_myDigits));
  3823                     UINT64 _myVal = (UINT64)(*((UINT *)_myDigits));
  3824 		    UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3824                     UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3825 		    RETURN( (_myVal <= _otherVal) ? true : false );
  3825                     RETURN( (_myVal <= _otherVal) ? true : false );
  3826 		}
  3826                 }
  3827 	    } else {
  3827             } else {
  3828 		if (_myLen <= 8) {
  3828                 if (_myLen <= 8) {
  3829 		    INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3829                     INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3830 
  3830 
  3831 		    if (_otherLen <= 8) {
  3831                     if (_otherLen <= 8) {
  3832 			UINT64 _myVal = (*((UINT64 *)_myDigits));
  3832                         UINT64 _myVal = (*((UINT64 *)_myDigits));
  3833 			UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3833                         UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3834 			RETURN( (_myVal <= _otherVal) ? true : false );
  3834                         RETURN( (_myVal <= _otherVal) ? true : false );
  3835 		    }
  3835                     }
  3836 		    if (_otherLen == __POINTER_SIZE__) {
  3836                     if (_otherLen == __POINTER_SIZE__) {
  3837 			UINT64 _myVal = (*((UINT64 *)_myDigits));
  3837                         UINT64 _myVal = (*((UINT64 *)_myDigits));
  3838 			UINT64 _otherVal = (UINT64) *((UINT *)_otherDigits);
  3838                         UINT64 _otherVal = (UINT64) *((UINT *)_otherDigits);
  3839 			RETURN( (_myVal <= _otherVal) ? true : false );
  3839                         RETURN( (_myVal <= _otherVal) ? true : false );
  3840 		    }
  3840                     }
  3841 		}
  3841                 }
  3842 	    }
  3842             }
  3843 # endif /* UINT64 */
  3843 # endif /* UINT64 */
  3844 	}
  3844         }
  3845     }
  3845     }
  3846 #endif /* LSBFIRST */
  3846 #endif /* LSBFIRST */
  3847 %}.
  3847 %}.
  3848 
  3848 
  3849     myLen := digitByteArray size.
  3849     myLen := digitByteArray size.
  3854     "/ when properly normalized;
  3854     "/ when properly normalized;
  3855     "/ but we are tolerant here, to allow for unnormalized
  3855     "/ but we are tolerant here, to allow for unnormalized
  3856     "/ numbers to be compared ...
  3856     "/ numbers to be compared ...
  3857 
  3857 
  3858     [(digitByteArray basicAt:myLen) == 0] whileTrue:[
  3858     [(digitByteArray basicAt:myLen) == 0] whileTrue:[
  3859 	myLen := myLen - 1
  3859         myLen := myLen - 1
  3860     ].
  3860     ].
  3861     [(otherDigitByteArray basicAt:otherLen) == 0] whileTrue:[
  3861     [(otherDigitByteArray basicAt:otherLen) == 0] whileTrue:[
  3862 	otherLen := otherLen - 1
  3862         otherLen := otherLen - 1
  3863     ].
  3863     ].
  3864     (myLen < otherLen) ifTrue:[^ true].
  3864     (myLen < otherLen) ifTrue:[^ true].
  3865     (myLen > otherLen) ifTrue:[^ false].
  3865     (myLen > otherLen) ifTrue:[^ false].
  3866 
  3866 
  3867     [myLen > 0] whileTrue:[
  3867     [myLen > 0] whileTrue:[
  3868 	d1 := digitByteArray basicAt:myLen.
  3868         d1 := digitByteArray basicAt:myLen.
  3869 	d2 := otherDigitByteArray basicAt:myLen.
  3869         d2 := otherDigitByteArray basicAt:myLen.
  3870 	d1 == d2 ifFalse:[
  3870         d1 == d2 ifFalse:[
  3871 	    (d1 < d2) ifTrue:[^ true].
  3871             (d1 < d2) ifTrue:[^ true].
  3872 	    ^ false.
  3872             ^ false.
  3873 	].
  3873         ].
  3874 	myLen := myLen - 1
  3874         myLen := myLen - 1
  3875     ].
  3875     ].
  3876     ^ true
  3876     ^ true
  3877 
  3877 
  3878     "Created: / 13.2.1998 / 12:19:45 / stefan"
  3878     "Created: / 13.2.1998 / 12:19:45 / stefan"
  3879     "Modified: / 30.4.1999 / 12:46:31 / stefan"
  3879     "Modified: / 30.4.1999 / 12:46:31 / stefan"
  4597 %{
  4597 %{
  4598     OBJ _digitByteArray = __INST(digitByteArray);
  4598     OBJ _digitByteArray = __INST(digitByteArray);
  4599 
  4599 
  4600     if (__isByteArray(_digitByteArray)
  4600     if (__isByteArray(_digitByteArray)
  4601      && __isByteArray(otherDigitByteArray)) {
  4601      && __isByteArray(otherDigitByteArray)) {
  4602 	int _len1, _len2, _newLen;
  4602         int _len1, _len2, _newLen;
  4603 	unsigned char *_myDigits, *_otherDigits, *_newDigits;
  4603         unsigned char *_myDigits, *_otherDigits, *_newDigits;
  4604 	int _index, _carry;
  4604         int _index, _carry;
  4605 	int _comLen;
  4605         int _comLen;
  4606 
  4606 
  4607 	_len1 = __byteArraySize(_digitByteArray);
  4607         _len1 = __byteArraySize(_digitByteArray);
  4608 	_len2 = __byteArraySize(otherDigitByteArray);
  4608         _len2 = __byteArraySize(otherDigitByteArray);
  4609 
  4609 
  4610 	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  4610         _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  4611 	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  4611         _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  4612 
  4612 
  4613 	if (_len1 < _len2) {
  4613         if (_len1 < _len2) {
  4614 	    _comLen = _len1;
  4614             _comLen = _len1;
  4615 	    _newLen = _len2;
  4615             _newLen = _len2;
  4616 	    if (_otherDigits[_len2 - 1] == 0xFF) _newLen++;
  4616             if (_otherDigits[_len2 - 1] == 0xFF) _newLen++;
  4617 	} else if (_len2 < _len1) {
  4617         } else if (_len2 < _len1) {
  4618 	    _comLen = _len2;
  4618             _comLen = _len2;
  4619 	    _newLen = _len1;
  4619             _newLen = _len1;
  4620 	    if (_myDigits[_len1 - 1] == 0xFF) _newLen++;
  4620             if (_myDigits[_len1 - 1] == 0xFF) _newLen++;
  4621 	} else {
  4621         } else {
  4622 	    /*
  4622             /*
  4623 	     * there can only be an overflow from the high bytes,
  4623              * there can only be an overflow from the high bytes,
  4624 	     * if their sum is >= 255
  4624              * if their sum is >= 255
  4625 	     * (with sum==255, a carry could still occur from the next lower bytes)
  4625              * (with sum==255, a carry could still occur from the next lower bytes)
  4626 	     */
  4626              */
  4627 	    _newLen = _len1;
  4627             _newLen = _len1;
  4628 	    if ((_otherDigits[_len2 - 1] + _myDigits[_len1 - 1]) >= 0xFF) {
  4628             if ((_otherDigits[_len2 - 1] + _myDigits[_len1 - 1]) >= 0xFF) {
  4629 		_newLen++;
  4629                 _newLen++;
  4630 	    } else {
  4630             } else {
  4631 		if (_newLen == sizeof(INT)) {
  4631                 if (_newLen == sizeof(INT)) {
  4632 		    OBJ _uint;
  4632                     OBJ _uint;
  4633 
  4633 
  4634 		    /*
  4634                     /*
  4635 		     * two word-sized numbers, no carry - a very common case ...
  4635                      * two word-sized numbers, no carry - a very common case ...
  4636 		     */
  4636                      */
  4637 #if defined(__LSB_FIRST__)
  4637 #if defined(__LSB_FIRST__)
  4638 		    unsigned INT _sum = *(unsigned INT *)_otherDigits + *(unsigned INT *)_myDigits;
  4638                     unsigned INT _sum = *(unsigned INT *)_otherDigits + *(unsigned INT *)_myDigits;
  4639 #else
  4639 #else
  4640 		    unsigned INT _sum = __unsignedLongIntVal(self) + __unsignedLongIntVal(aLargeInteger);
  4640                     unsigned INT _sum = __unsignedLongIntVal(self) + __unsignedLongIntVal(aLargeInteger);
  4641 #endif /* not LSB_FIRST */
  4641 #endif /* not LSB_FIRST */
  4642 		    if (_sum <= _MAX_INT) {
  4642                     if (_sum <= _MAX_INT) {
  4643 			_uint = __mkSmallInteger(_sum * __intVal(newSign));
  4643                         _uint = __mkSmallInteger(_sum * __intVal(newSign));
  4644 		    } else {
  4644                     } else {
  4645 			_uint = __MKULARGEINT(_sum);
  4645                         _uint = __MKULARGEINT(_sum);
  4646 			__LargeIntegerInstPtr(_uint)->l_sign = newSign;
  4646                         __LargeIntegerInstPtr(_uint)->l_sign = newSign;
  4647 		    }
  4647                     }
  4648 		    RETURN (_uint);
  4648                     RETURN (_uint);
  4649 		}
  4649                 }
  4650 	    }
  4650             }
  4651 	    _comLen = _len1;
  4651             _comLen = _len1;
  4652 	}
  4652         }
  4653 	resultDigitByteArray = __BYTEARRAY_UNINITIALIZED_NEW_INT(_newLen);
  4653         resultDigitByteArray = __BYTEARRAY_UNINITIALIZED_NEW_INT(_newLen);
  4654 
  4654 
  4655 	/*
  4655         /*
  4656 	 * must refetch - GC could have been invoked
  4656          * must refetch - GC could have been invoked
  4657 	 */
  4657          */
  4658 	_digitByteArray = __INST(digitByteArray);
  4658         _digitByteArray = __INST(digitByteArray);
  4659 
  4659 
  4660 	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  4660         _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  4661 	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  4661         _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  4662 	_newDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  4662         _newDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  4663 
  4663 
  4664 	/*
  4664         /*
  4665 	 * add them ...
  4665          * add them ...
  4666 	 */
  4666          */
  4667 	_index = 1;
  4667         _index = 1;
  4668 	_carry = 0;
  4668         _carry = 0;
  4669 
  4669 
  4670 #if defined(__LSBFIRST__)
  4670 #if defined(__LSBFIRST__)
  4671 # if (__POINTER_SIZE__ == 8) && defined(__GNUC__)
  4671 # if (__POINTER_SIZE__ == 8) && defined(__GNUC__)
  4672 #  if 0  /* not faster (on alpha) */
  4672 #  if 0  /* not faster (on alpha) */
  4673 	{
  4673         {
  4674 	    int _comLen7;
  4674             int _comLen7;
  4675 
  4675 
  4676 	    /*
  4676             /*
  4677 	     * have a 64bit integers;
  4677              * have a 64bit integers;
  4678 	     * add quad-wise
  4678              * add quad-wise
  4679 	     * accessing bytes at: [index-1][index][index+1]..[index+6]
  4679              * accessing bytes at: [index-1][index][index+1]..[index+6]
  4680 	     */
  4680              */
  4681 	    _comLen7 = _comLen - 3 - 4;
  4681             _comLen7 = _comLen - 3 - 4;
  4682 	    while (_index <= _comLen7) {
  4682             while (_index <= _comLen7) {
  4683 		UINT64 _sum, _t1, _t2;
  4683                 UINT64 _sum, _t1, _t2;
  4684 
  4684 
  4685 		asm ("addq   %5,%6,%1         /* sum */                  \n\
  4685                 asm ("addq   %5,%6,%1         /* sum */                  \n\
  4686 		      addq   %0,%1,%1         /* plus carryIn */         \n\
  4686                       addq   %0,%1,%1         /* plus carryIn */         \n\
  4687 		      cmpult %1,%5,%2         /* was there a carry ? */  \n\
  4687                       cmpult %1,%5,%2         /* was there a carry ? */  \n\
  4688 		      cmpult %1,%6,%3         /* was there a carry ? */  \n\
  4688                       cmpult %1,%6,%3         /* was there a carry ? */  \n\
  4689 		      bis    %2,%3,%0         /* carryOut */             \n\
  4689                       bis    %2,%3,%0         /* carryOut */             \n\
  4690 		     "
  4690                      "
  4691 			: "=r"  (_carry),
  4691                         : "=r"  (_carry),
  4692 			  "=r"  (_sum),
  4692                           "=r"  (_sum),
  4693 			  "r"   (_t1),
  4693                           "r"   (_t1),
  4694 			  "r"   (_t2)
  4694                           "r"   (_t2)
  4695 			: "r"   (_carry),
  4695                         : "r"   (_carry),
  4696 			  "r"   (((unsigned long *)(&(_myDigits[_index - 1])))[0]),
  4696                           "r"   (((unsigned long *)(&(_myDigits[_index - 1])))[0]),
  4697 			  "r"   (((unsigned long *)(&(_otherDigits[_index - 1])))[0])
  4697                           "r"   (((unsigned long *)(&(_otherDigits[_index - 1])))[0])
  4698 		    );
  4698                     );
  4699 		/* _sum = _sum & 0xFFFFFFFF; */
  4699                 /* _sum = _sum & 0xFFFFFFFF; */
  4700 		((unsigned long *)(&(_newDigits[_index - 1])))[0] = _sum;
  4700                 ((unsigned long *)(&(_newDigits[_index - 1])))[0] = _sum;
  4701 		_index += 8;
  4701                 _index += 8;
  4702 	    }
  4702             }
  4703 	}
  4703         }
  4704 #  endif
  4704 #  endif
  4705 # endif /* 64bit */
  4705 # endif /* 64bit */
  4706 
  4706 
  4707 # if (__POINTER_SIZE__ == 8)
  4707 # if (__POINTER_SIZE__ == 8)
  4708 # if 0  /* not faster (on alpha) */
  4708 # if 0  /* not faster (on alpha) */
  4709 	{
  4709         {
  4710 	    int _comLen7;
  4710             int _comLen7;
  4711 
  4711 
  4712 	    /*
  4712             /*
  4713 	     * have a 64bit integers;
  4713              * have a 64bit integers;
  4714 	     * add quad-wise
  4714              * add quad-wise
  4715 	     * accessing bytes at: [index-1][index][index+1]..[index+6]
  4715              * accessing bytes at: [index-1][index][index+1]..[index+6]
  4716 	     */
  4716              */
  4717 	    _comLen7 = _comLen - 3 - 4;
  4717             _comLen7 = _comLen - 3 - 4;
  4718 	    while (_index <= _comLen7) {
  4718             while (_index <= _comLen7) {
  4719 		UINT64 _sum, _t1, _t2;
  4719                 UINT64 _sum, _t1, _t2;
  4720 
  4720 
  4721 		_t1 = ((UINT64 *)(&(_myDigits[_index - 1])))[0];
  4721                 _t1 = ((UINT64 *)(&(_myDigits[_index - 1])))[0];
  4722 		_t2 = ((UINT64 *)(&(_otherDigits[_index - 1])))[0];
  4722                 _t2 = ((UINT64 *)(&(_otherDigits[_index - 1])))[0];
  4723 		_sum = _t1 + _t2 + _carry;
  4723                 _sum = _t1 + _t2 + _carry;
  4724 		((UINT64 *)(&(_newDigits[_index - 1])))[0] = _sum;
  4724                 ((UINT64 *)(&(_newDigits[_index - 1])))[0] = _sum;
  4725 		_carry = (_sum < _t1) | (_sum < _t2);
  4725                 _carry = (_sum < _t1) | (_sum < _t2);
  4726 		_index += 8;
  4726                 _index += 8;
  4727 	    }
  4727             }
  4728 	}
  4728         }
  4729 #  endif
  4729 #  endif
  4730 # endif /* 64bit */
  4730 # endif /* 64bit */
  4731 
  4731 
  4732 # ifdef UINT64
  4732 # ifdef UINT64
  4733 	{
  4733         {
  4734 	    int _comLen3;
  4734             int _comLen3;
  4735 
  4735 
  4736 	    /*
  4736             /*
  4737 	     * have a 64bit integer type;
  4737              * have a 64bit integer type;
  4738 	     * add int-wise
  4738              * add int-wise
  4739 	     * accessing bytes at: [index-1][index][index+1][index+2]
  4739              * accessing bytes at: [index-1][index][index+1][index+2]
  4740 	     */
  4740              */
  4741 	    _comLen3 = _comLen - 3;
  4741             _comLen3 = _comLen - 3;
  4742 	    while (_index <= _comLen3) {
  4742             while (_index <= _comLen3) {
  4743 		UINT64 _sum;
  4743                 UINT64 _sum;
  4744 
  4744 
  4745 		/* do not merge the 3 lines below into one -
  4745                 /* do not merge the 3 lines below into one -
  4746 		 * (will do sign extension then, which is wrong here)
  4746                  * (will do sign extension then, which is wrong here)
  4747 		 */
  4747                  */
  4748 		_sum = (unsigned)_carry;
  4748                 _sum = (unsigned)_carry;
  4749 		_sum += ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4749                 _sum += ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4750 		_sum += ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4750                 _sum += ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4751 		_carry = _sum >> 32;
  4751                 _carry = _sum >> 32;
  4752 		/* _sum = _sum & 0xFFFFFFFF; */
  4752                 /* _sum = _sum & 0xFFFFFFFF; */
  4753 		((unsigned int *)(&(_newDigits[_index - 1])))[0] = _sum;
  4753                 ((unsigned int *)(&(_newDigits[_index - 1])))[0] = _sum;
  4754 		_index += 4;
  4754                 _index += 4;
  4755 	    }
  4755             }
  4756 	}
  4756         }
  4757 # else
  4757 # else
  4758 #  if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
  4758 #  if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
  4759 	{
  4759         {
  4760 	    int _comLen3;
  4760             int _comLen3;
  4761 
  4761 
  4762 	    _comLen3 = _comLen - 3 - 4;
  4762             _comLen3 = _comLen - 3 - 4;
  4763 	    while (_index <= _comLen3) {
  4763             while (_index <= _comLen3) {
  4764 		unsigned int _sum, _sum2;
  4764                 unsigned int _sum, _sum2;
  4765 		unsigned int __in1A, __in1B, __in2A, __in2B;
  4765                 unsigned int __in1A, __in1B, __in2A, __in2B;
  4766 
  4766 
  4767 		__in1A = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4767                 __in1A = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4768 		__in2A = ((unsigned int *)(&(_myDigits[_index - 1])))[1];
  4768                 __in2A = ((unsigned int *)(&(_myDigits[_index - 1])))[1];
  4769 		__in1B = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4769                 __in1B = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4770 		__in2B = ((unsigned int *)(&(_otherDigits[_index - 1])))[1];
  4770                 __in2B = ((unsigned int *)(&(_otherDigits[_index - 1])))[1];
  4771 
  4771 
  4772 		asm ("addl %%edx,%%eax  \n\
  4772                 asm ("addl %%edx,%%eax  \n\
  4773 		      movl $0,%%edx     \n\
  4773                       movl $0,%%edx     \n\
  4774 		      adcl $0,%%edx     \n\
  4774                       adcl $0,%%edx     \n\
  4775 		      addl %5,%%eax     \n\
  4775                       addl %5,%%eax     \n\
  4776 		      adcl $0,%%edx     \n\
  4776                       adcl $0,%%edx     \n\
  4777 					\n\
  4777                                         \n\
  4778 		      addl %%edx,%%ecx  \n\
  4778                       addl %%edx,%%ecx  \n\
  4779 		      movl $0,%%edx     \n\
  4779                       movl $0,%%edx     \n\
  4780 		      adcl $0,%%edx     \n\
  4780                       adcl $0,%%edx     \n\
  4781 		      addl %7,%%ecx     \n\
  4781                       addl %7,%%ecx     \n\
  4782 		      adcl $0,%%edx     \n\
  4782                       adcl $0,%%edx     \n\
  4783 		     "
  4783                      "
  4784 			: "=d"  (_carry),
  4784                         : "=d"  (_carry),
  4785 			  "=a"  (_sum),
  4785                           "=a"  (_sum),
  4786 			  "=c"  (_sum2)
  4786                           "=c"  (_sum2)
  4787 			: "0"   (_carry),
  4787                         : "0"   (_carry),
  4788 			  "1"   (__in1A),
  4788                           "1"   (__in1A),
  4789 			  "rm"  (__in1B),
  4789                           "rm"  (__in1B),
  4790 			  "2"   (__in2A),
  4790                           "2"   (__in2A),
  4791 			  "rm"  (__in2B)
  4791                           "rm"  (__in2B)
  4792 		    );
  4792                     );
  4793 
  4793 
  4794 		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4794                 ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4795 		((unsigned *)(&(_newDigits[_index - 1])))[1] = _sum2;
  4795                 ((unsigned *)(&(_newDigits[_index - 1])))[1] = _sum2;
  4796 		_index += 8;
  4796                 _index += 8;
  4797 	    }
  4797             }
  4798 	    /*
  4798             /*
  4799 	     * add int-wise
  4799              * add int-wise
  4800 	     * accessing bytes at: [index-1][index][index+1][index+2]
  4800              * accessing bytes at: [index-1][index][index+1][index+2]
  4801 	     */
  4801              */
  4802 	    _comLen3 = _comLen3 + 4;
  4802             _comLen3 = _comLen3 + 4;
  4803 	    if (_index <= _comLen3) {
  4803             if (_index <= _comLen3) {
  4804 		unsigned int _sum;
  4804                 unsigned int _sum;
  4805 		unsigned int __inA, __inB;
  4805                 unsigned int __inA, __inB;
  4806 
  4806 
  4807 		__inA = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4807                 __inA = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4808 		__inB = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4808                 __inB = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4809 
  4809 
  4810 		asm ("addl %%edx,%%eax      \n\
  4810                 asm ("addl %%edx,%%eax      \n\
  4811 		      movl $0,%%edx         \n\
  4811                       movl $0,%%edx         \n\
  4812 		      adcl $0,%%edx         \n\
  4812                       adcl $0,%%edx         \n\
  4813 		      addl %4,%%eax         \n\
  4813                       addl %4,%%eax         \n\
  4814 		      adcl $0,%%edx"
  4814                       adcl $0,%%edx"
  4815 			: "=d"  (_carry),
  4815                         : "=d"  (_carry),
  4816 			  "=a"  (_sum)
  4816                           "=a"  (_sum)
  4817 			: "0"   (_carry),
  4817                         : "0"   (_carry),
  4818 			  "1"   (__inA),
  4818                           "1"   (__inA),
  4819 			  "rm"  (__inB)
  4819                           "rm"  (__inB)
  4820 		    );
  4820                     );
  4821 
  4821 
  4822 		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4822                 ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4823 		_index += 4;
  4823                 _index += 4;
  4824 	    }
  4824             }
  4825 	}
  4825         }
  4826 #  endif /* __i386__ && GNUC */
  4826 #  endif /* __i386__ && GNUC */
  4827 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  4827 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  4828 	{
  4828         {
  4829 	    int _comLen3;
  4829             int _comLen3;
  4830 
  4830 
  4831 	    /*
  4831             /*
  4832 	     * add long-wise
  4832              * add long-wise
  4833 	     * accessing bytes at: [index-1][index][index+1][index+2]
  4833              * accessing bytes at: [index-1][index][index+1][index+2]
  4834 	     */
  4834              */
  4835 	    _comLen3 = _comLen - 3;
  4835             _comLen3 = _comLen - 3;
  4836 	    while (_index <= _comLen3) {
  4836             while (_index <= _comLen3) {
  4837 		unsigned int _sum, _v1, _v2;
  4837                 unsigned int _sum, _v1, _v2;
  4838 
  4838 
  4839 		_v1 = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4839                 _v1 = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4840 		_v2 = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4840                 _v2 = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4841 		asm {
  4841                 asm {
  4842 		      mov eax, _v1
  4842                       mov eax, _v1
  4843 		      add eax, _v2
  4843                       add eax, _v2
  4844 		      mov edx, 0
  4844                       mov edx, 0
  4845 		      adc edx, 0
  4845                       adc edx, 0
  4846 		      add eax, _carry
  4846                       add eax, _carry
  4847 		      adc edx, 0
  4847                       adc edx, 0
  4848 		      mov _carry, edx
  4848                       mov _carry, edx
  4849 		      mov _sum, eax
  4849                       mov _sum, eax
  4850 		    }
  4850                     }
  4851 
  4851 
  4852 		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4852                 ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4853 		_index += 4;
  4853                 _index += 4;
  4854 	    }
  4854             }
  4855 	}
  4855         }
  4856 #  endif /* __i386__ && WIN32 */
  4856 #  endif /* __i386__ && WIN32 */
  4857 # endif /* INT64 */
  4857 # endif /* INT64 */
  4858 	/*
  4858         /*
  4859 	 * add short-wise
  4859          * add short-wise
  4860 	 * accessing bytes at: [index-1][index]
  4860          * accessing bytes at: [index-1][index]
  4861 	 */
  4861          */
  4862 	while (_index < _comLen) {
  4862         while (_index < _comLen) {
  4863 	    unsigned int _sum;
  4863             unsigned int _sum;
  4864 
  4864 
  4865 	    _sum = _carry
  4865             _sum = _carry
  4866 		   + ((unsigned short *)(&(_myDigits[_index - 1])))[0]
  4866                    + ((unsigned short *)(&(_myDigits[_index - 1])))[0]
  4867 		   + ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
  4867                    + ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
  4868 	    _carry = _sum >> 16;
  4868             _carry = _sum >> 16;
  4869 	    /* _sum = _sum & 0xFFFF; */
  4869             /* _sum = _sum & 0xFFFF; */
  4870 	    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4870             *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4871 	    _index += 2;
  4871             _index += 2;
  4872 	}
  4872         }
  4873 #else
  4873 #else
  4874 # ifdef __sparc__
  4874 # ifdef __sparc__
  4875 	/*
  4875         /*
  4876 	 * add short-wise
  4876          * add short-wise
  4877 	 * accessing bytes at: [index-1][index]
  4877          * accessing bytes at: [index-1][index]
  4878 	 */
  4878          */
  4879 	while (_index < _comLen) {
  4879         while (_index < _comLen) {
  4880 	    unsigned int _sum;
  4880             unsigned int _sum;
  4881 	    unsigned short _v1, _v2;
  4881             unsigned short _v1, _v2;
  4882 
  4882 
  4883 	    _v1 = ((unsigned short *)(&(_myDigits[_index - 1])))[0];
  4883             _v1 = ((unsigned short *)(&(_myDigits[_index - 1])))[0];
  4884 	    _v2 = ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
  4884             _v2 = ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
  4885 	    _sum = _carry + (_v1>>8) + (_v2>>8);
  4885             _sum = _carry + (_v1>>8) + (_v2>>8);
  4886 	    _carry = _sum >> 8;
  4886             _carry = _sum >> 8;
  4887 	    _newDigits[_index - 1] = _sum;
  4887             _newDigits[_index - 1] = _sum;
  4888 
  4888 
  4889 	    _sum = _carry + (_v1 & 0xFF) + (_v2 & 0xFF);
  4889             _sum = _carry + (_v1 & 0xFF) + (_v2 & 0xFF);
  4890 	    _carry = _sum >> 8;
  4890             _carry = _sum >> 8;
  4891 	    _newDigits[_index] = _sum;
  4891             _newDigits[_index] = _sum;
  4892 	    _index += 2;
  4892             _index += 2;
  4893 	}
  4893         }
  4894 # endif
  4894 # endif
  4895 #endif /* __LSBFIRST__ */
  4895 #endif /* __LSBFIRST__ */
  4896 
  4896 
  4897 	/*
  4897         /*
  4898 	 * add byte-wise
  4898          * add byte-wise
  4899 	 */
  4899          */
  4900 	while (_index <= _comLen) {
  4900         while (_index <= _comLen) {
  4901 	    unsigned int _sum;
  4901             unsigned int _sum;
  4902 
  4902 
  4903 	    _sum = _carry
  4903             _sum = _carry
  4904 		   + _myDigits[_index - 1]
  4904                    + _myDigits[_index - 1]
  4905 		   + _otherDigits[_index - 1];
  4905                    + _otherDigits[_index - 1];
  4906 	    _carry = _sum >> 8;
  4906             _carry = _sum >> 8;
  4907 	    /* _sum = _sum & 0xFF; */
  4907             /* _sum = _sum & 0xFF; */
  4908 	    _newDigits[_index - 1] = _sum;
  4908             _newDigits[_index - 1] = _sum;
  4909 	    _index++;
  4909             _index++;
  4910 	}
  4910         }
  4911 
  4911 
  4912 	/*
  4912         /*
  4913 	 * rest
  4913          * rest
  4914 	 */
  4914          */
  4915 	if (_len1 > _len2) {
  4915         if (_len1 > _len2) {
  4916 #if defined(__LSBFIRST__)
  4916 #if defined(__LSBFIRST__)
  4917 	    if (_index <= _len1) {
  4917             if (_index <= _len1) {
  4918 		if ((_index - 1) & 1) {
  4918                 if ((_index - 1) & 1) {
  4919 		    /* odd byte */
  4919                     /* odd byte */
  4920 		    unsigned int _sum;
  4920                     unsigned int _sum;
  4921 
  4921 
  4922 		    _sum = _carry + _myDigits[_index - 1];
  4922                     _sum = _carry + _myDigits[_index - 1];
  4923 		    _carry = _sum >> 8;
  4923                     _carry = _sum >> 8;
  4924 		    /* _sum = _sum & 0xFF; */
  4924                     /* _sum = _sum & 0xFF; */
  4925 		    _newDigits[_index - 1] = _sum;
  4925                     _newDigits[_index - 1] = _sum;
  4926 		    _index++;
  4926                     _index++;
  4927 		}
  4927                 }
  4928 
  4928 
  4929 		while (_index < _len1) {
  4929                 while (_index < _len1) {
  4930 		    /* shorts */
  4930                     /* shorts */
  4931 		    unsigned int _sum;
  4931                     unsigned int _sum;
  4932 
  4932 
  4933 		    _sum = _carry + *(unsigned short *)(&(_myDigits[_index - 1]));
  4933                     _sum = _carry + *(unsigned short *)(&(_myDigits[_index - 1]));
  4934 		    _carry = _sum >> 16;
  4934                     _carry = _sum >> 16;
  4935 		    /* _sum = _sum & 0xFFFF; */
  4935                     /* _sum = _sum & 0xFFFF; */
  4936 		    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4936                     *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4937 		    _index += 2;
  4937                     _index += 2;
  4938 		}
  4938                 }
  4939 
  4939 
  4940 		if (_index <= _len1) {
  4940                 if (_index <= _len1) {
  4941 		    /* last byte */
  4941                     /* last byte */
  4942 		    unsigned int _sum;
  4942                     unsigned int _sum;
  4943 
  4943 
  4944 		    _sum = _carry + _myDigits[_index - 1];
  4944                     _sum = _carry + _myDigits[_index - 1];
  4945 		    _carry = _sum >> 8;
  4945                     _carry = _sum >> 8;
  4946 		    /* _sum = _sum & 0xFF; */
  4946                     /* _sum = _sum & 0xFF; */
  4947 		    _newDigits[_index - 1] = _sum;
  4947                     _newDigits[_index - 1] = _sum;
  4948 		    _index++;
  4948                     _index++;
  4949 		}
  4949                 }
  4950 	    }
  4950             }
  4951 #else
  4951 #else
  4952 	    while (_index <= _len1) {
  4952             while (_index <= _len1) {
  4953 		unsigned int _sum;
  4953                 unsigned int _sum;
  4954 
  4954 
  4955 		_sum = _carry + _myDigits[_index - 1];
  4955                 _sum = _carry + _myDigits[_index - 1];
  4956 		_carry = _sum >> 8;
  4956                 _carry = _sum >> 8;
  4957 		/* _sum = _sum & 0xFF; */
  4957                 /* _sum = _sum & 0xFF; */
  4958 		_newDigits[_index - 1] = _sum;
  4958                 _newDigits[_index - 1] = _sum;
  4959 		_index++;
  4959                 _index++;
  4960 	    }
  4960             }
  4961 #endif /* not LSB */
  4961 #endif /* not LSB */
  4962 	} else {
  4962         } else {
  4963 	    if (_len2 > _len1) {
  4963             if (_len2 > _len1) {
  4964 #if defined(__LSBFIRST__)
  4964 #if defined(__LSBFIRST__)
  4965 		if (_index <= _len2) {
  4965                 if (_index <= _len2) {
  4966 		    if ((_index - 1) & 1) {
  4966                     if ((_index - 1) & 1) {
  4967 			/* odd byte */
  4967                         /* odd byte */
  4968 			unsigned int _sum;
  4968                         unsigned int _sum;
  4969 
  4969 
  4970 			_sum = _carry + _otherDigits[_index - 1];
  4970                         _sum = _carry + _otherDigits[_index - 1];
  4971 			_carry = _sum >> 8;
  4971                         _carry = _sum >> 8;
  4972 			/* _sum = _sum & 0xFF; */
  4972                         /* _sum = _sum & 0xFF; */
  4973 			_newDigits[_index - 1] = _sum;
  4973                         _newDigits[_index - 1] = _sum;
  4974 			_index++;
  4974                         _index++;
  4975 		    }
  4975                     }
  4976 
  4976 
  4977 		    while (_index < _len2) {
  4977                     while (_index < _len2) {
  4978 			/* shorts */
  4978                         /* shorts */
  4979 			unsigned int _sum;
  4979                         unsigned int _sum;
  4980 
  4980 
  4981 			_sum = _carry + *(unsigned short *)(&(_otherDigits[_index - 1]));
  4981                         _sum = _carry + *(unsigned short *)(&(_otherDigits[_index - 1]));
  4982 			_carry = _sum >> 16;
  4982                         _carry = _sum >> 16;
  4983 			/* _sum = _sum & 0xFFFF; */
  4983                         /* _sum = _sum & 0xFFFF; */
  4984 			*(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4984                         *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4985 			_index += 2;
  4985                         _index += 2;
  4986 		    }
  4986                     }
  4987 
  4987 
  4988 		    if (_index <= _len2) {
  4988                     if (_index <= _len2) {
  4989 			/* last byte */
  4989                         /* last byte */
  4990 			unsigned int _sum;
  4990                         unsigned int _sum;
  4991 
  4991 
  4992 			_sum = _carry + _otherDigits[_index - 1];
  4992                         _sum = _carry + _otherDigits[_index - 1];
  4993 			_carry = _sum >> 8;
  4993                         _carry = _sum >> 8;
  4994 			/* _sum = _sum & 0xFF; */
  4994                         /* _sum = _sum & 0xFF; */
  4995 			_newDigits[_index - 1] = _sum;
  4995                         _newDigits[_index - 1] = _sum;
  4996 			_index++;
  4996                         _index++;
  4997 		    }
  4997                     }
  4998 		}
  4998                 }
  4999 #else
  4999 #else
  5000 		while (_index <= _len2) {
  5000                 while (_index <= _len2) {
  5001 		    unsigned int _sum;
  5001                     unsigned int _sum;
  5002 
  5002 
  5003 		    _sum = _carry + _otherDigits[_index - 1];
  5003                     _sum = _carry + _otherDigits[_index - 1];
  5004 		    _carry = _sum >> 8;
  5004                     _carry = _sum >> 8;
  5005 		    /* _sum = _sum & 0xFF; */
  5005                     /* _sum = _sum & 0xFF; */
  5006 		    _newDigits[_index - 1] = _sum;
  5006                     _newDigits[_index - 1] = _sum;
  5007 		    _index++;
  5007                     _index++;
  5008 		}
  5008                 }
  5009 #endif /* not LSB */
  5009 #endif /* not LSB */
  5010 	    }
  5010             }
  5011 	}
  5011         }
  5012 
  5012 
  5013 	while (_index <= _newLen) {
  5013         while (_index <= _newLen) {
  5014 	    unsigned int _sum;
  5014             unsigned int _sum;
  5015 
  5015 
  5016 	    _sum = _carry;
  5016             _sum = _carry;
  5017 	    _carry = _sum >> 8;
  5017             _carry = _sum >> 8;
  5018 	    /* _sum = _sum & 0xFF; */
  5018             /* _sum = _sum & 0xFF; */
  5019 	    _newDigits[_index - 1] = _sum;
  5019             _newDigits[_index - 1] = _sum;
  5020 	    _index++;
  5020             _index++;
  5021 	}
  5021         }
  5022     }
  5022     }
  5023 %}.
  5023 %}.
  5024     resultDigitByteArray notNil ifTrue:[
  5024     resultDigitByteArray notNil ifTrue:[
  5025 	result := self class basicNew.
  5025         result := self class basicNew.
  5026 	result setDigits:resultDigitByteArray.
  5026         result setDigits:resultDigitByteArray.
  5027 	result setSign:newSign.
  5027         result setSign:newSign.
  5028     ] ifFalse:[
  5028     ] ifFalse:[
  5029 	len1 := digitByteArray size.
  5029         len1 := digitByteArray size.
  5030 	len2 := otherDigitByteArray size.
  5030         len2 := otherDigitByteArray size.
  5031 
  5031 
  5032 	"/ earlier versions estimated the newLength as:
  5032         "/ earlier versions estimated the newLength as:
  5033 	"/ (len1 max:len2) + 1
  5033         "/ (len1 max:len2) + 1
  5034 	"/ and reduced the result.
  5034         "/ and reduced the result.
  5035 	"/ however, if one of the addends is smaller,
  5035         "/ however, if one of the addends is smaller,
  5036 	"/ the result will never require another digit,
  5036         "/ the result will never require another digit,
  5037 	"/ if the highest digit of the larger addent is
  5037         "/ if the highest digit of the larger addent is
  5038 	"/ not equal to 255. Therefore, in most cases,
  5038         "/ not equal to 255. Therefore, in most cases,
  5039 	"/ we can avoid the computation and resizing
  5039         "/ we can avoid the computation and resizing
  5040 	"/ in #reduced.
  5040         "/ in #reduced.
  5041 
  5041 
  5042 	len1 < len2 ifTrue:[
  5042         len1 < len2 ifTrue:[
  5043 	    newLen := len2.
  5043             newLen := len2.
  5044 	    (otherDigitByteArray at:len2) == 16rFF ifTrue:[
  5044             (otherDigitByteArray at:len2) == 16rFF ifTrue:[
  5045 		newLen := newLen + 1
  5045                 newLen := newLen + 1
  5046 	    ]
  5046             ]
  5047 	] ifFalse:[
  5047         ] ifFalse:[
  5048 	    len2 < len1 ifTrue:[
  5048             len2 < len1 ifTrue:[
  5049 		newLen := len1.
  5049                 newLen := len1.
  5050 		(digitByteArray at:len1) == 16rFF ifTrue:[
  5050                 (digitByteArray at:len1) == 16rFF ifTrue:[
  5051 		    newLen := newLen + 1
  5051                     newLen := newLen + 1
  5052 		]
  5052                 ]
  5053 	    ] ifFalse:[
  5053             ] ifFalse:[
  5054 		newLen := len1 + 1.
  5054                 newLen := len1 + 1.
  5055 	    ]
  5055             ]
  5056 	].
  5056         ].
  5057 
  5057 
  5058 	result := self class basicNew numberOfDigits:newLen.
  5058         result := self class basicNew numberOfDigits:newLen.
  5059 	result sign:newSign.
  5059         result sign:newSign.
  5060 	resultDigitByteArray := result digitBytes.
  5060         resultDigitByteArray := result digitBytes.
  5061 
  5061 
  5062 	index := 1.
  5062         index := 1.
  5063 	carry := 0.
  5063         carry := 0.
  5064 
  5064 
  5065 	done := false.
  5065         done := false.
  5066 	[done] whileFalse:[
  5066         [done] whileFalse:[
  5067 	    sum := carry.
  5067             sum := carry.
  5068 	    (index <= len1) ifTrue:[
  5068             (index <= len1) ifTrue:[
  5069 		sum := sum + (digitByteArray basicAt:index).
  5069                 sum := sum + (digitByteArray basicAt:index).
  5070 		(index <= len2) ifTrue:[
  5070                 (index <= len2) ifTrue:[
  5071 		    sum := sum + (otherDigitByteArray basicAt:index)
  5071                     sum := sum + (otherDigitByteArray basicAt:index)
  5072 		]
  5072                 ]
  5073 	    ] ifFalse:[
  5073             ] ifFalse:[
  5074 		(index <= len2) ifTrue:[
  5074                 (index <= len2) ifTrue:[
  5075 		    sum := sum + (otherDigitByteArray basicAt:index)
  5075                     sum := sum + (otherDigitByteArray basicAt:index)
  5076 		] ifFalse:[
  5076                 ] ifFalse:[
  5077 		    "end reached"
  5077                     "end reached"
  5078 		    done := true
  5078                     done := true
  5079 		]
  5079                 ]
  5080 	    ].
  5080             ].
  5081 	    (sum >= 16r100) ifTrue:[
  5081             (sum >= 16r100) ifTrue:[
  5082 		carry := 1.
  5082                 carry := 1.
  5083 		sum := sum - 16r100
  5083                 sum := sum - 16r100
  5084 	    ] ifFalse:[
  5084             ] ifFalse:[
  5085 		carry := 0
  5085                 carry := 0
  5086 	    ].
  5086             ].
  5087 	    resultDigitByteArray basicAt:index put:sum.
  5087             resultDigitByteArray basicAt:index put:sum.
  5088 	    index := index + 1
  5088             index := index + 1
  5089 	].
  5089         ].
  5090     ].
  5090     ].
  5091 
  5091 
  5092     ^ result compressed
  5092     ^ result compressed
  5093 
  5093 
  5094     "Modified: 11.8.1997 / 03:23:37 / cg"
  5094     "Modified: 11.8.1997 / 03:23:37 / cg"
  5095 !
  5095 !
  5096 
  5096 
  5097 absSubtract:aLargeInteger
  5097 absSubtract:aLargeInteger
  5098     "private helper for division:
  5098     "private helper for division:
  5099 	destructively subtract aLargeInteger from myself
  5099         destructively subtract aLargeInteger from myself
  5100 	AND return true, if the result is non-zero, false otherwise.
  5100         AND return true, if the result is non-zero, false otherwise.
  5101 	(i.e. this method has both a return value and a side-effect
  5101         (i.e. this method has both a return value and a side-effect
  5102 	 on the receiver)
  5102          on the receiver)
  5103 	Only allowed for positive receiver and argument
  5103         Only allowed for positive receiver and argument
  5104 	The receiver must be >= the argument.
  5104         The receiver must be >= the argument.
  5105 	The receiver must be a temporary scratch-number"
  5105         The receiver must be a temporary scratch-number"
  5106 
  5106 
  5107     |otherDigitByteArray
  5107     |otherDigitByteArray
  5108      len1   "{ Class: SmallInteger }"
  5108      len1   "{ Class: SmallInteger }"
  5109      len2   "{ Class: SmallInteger }"
  5109      len2   "{ Class: SmallInteger }"
  5110      index  "{ Class: SmallInteger }"
  5110      index  "{ Class: SmallInteger }"
  5116     notZero := false.
  5116     notZero := false.
  5117     len1 := digitByteArray size.
  5117     len1 := digitByteArray size.
  5118     otherDigitByteArray := aLargeInteger digitBytes.
  5118     otherDigitByteArray := aLargeInteger digitBytes.
  5119     len2 := otherDigitByteArray size.
  5119     len2 := otherDigitByteArray size.
  5120     len2 > len1 ifTrue:[
  5120     len2 > len1 ifTrue:[
  5121 	[(otherDigitByteArray at:len2) == 0] whileTrue:[
  5121         [(otherDigitByteArray at:len2) == 0] whileTrue:[
  5122 	    len2 := len2 - 1
  5122             len2 := len2 - 1
  5123 	].
  5123         ].
  5124 	len2 > len1 ifTrue:[
  5124         len2 > len1 ifTrue:[
  5125 	    self error:'operation failed' "/ may not be called that way
  5125             self error:'operation failed' "/ may not be called that way
  5126 	].
  5126         ].
  5127     ].
  5127     ].
  5128     "/ knowing that len2 is <= len1
  5128     "/ knowing that len2 is <= len1
  5129 %{
  5129 %{
  5130 
  5130 
  5131     OBJ _digitByteArray = __INST(digitByteArray);
  5131     OBJ _digitByteArray = __INST(digitByteArray);
  5132 
  5132 
  5133     if (__isByteArray(_digitByteArray)
  5133     if (__isByteArray(_digitByteArray)
  5134      && __isByteArray(otherDigitByteArray)) {
  5134      && __isByteArray(otherDigitByteArray)) {
  5135 	int _len1 = __intVal(len1),
  5135         int _len1 = __intVal(len1),
  5136 	    _len2 = __intVal(len2);
  5136             _len2 = __intVal(len2);
  5137 	unsigned char *_myDigits, *_otherDigits;
  5137         unsigned char *_myDigits, *_otherDigits;
  5138 	int _index = 1, _borrow = 0;
  5138         int _index = 1, _borrow = 0;
  5139 	INT _diff;
  5139         INT _diff;
  5140 	int anyBitNonZero = 0;
  5140         int anyBitNonZero = 0;
  5141 
  5141 
  5142 	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  5142         _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  5143 	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  5143         _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  5144 
  5144 
  5145 #if defined(__LSBFIRST__)
  5145 #if defined(__LSBFIRST__)
  5146 # if __POINTER_SIZE__ == 8
  5146 # if __POINTER_SIZE__ == 8
  5147 	{
  5147         {
  5148 	    int _len2Q;
  5148             int _len2Q;
  5149 	    /*
  5149             /*
  5150 	     * subtract int-wise
  5150              * subtract int-wise
  5151 	     */
  5151              */
  5152 	    _len2Q = _len2-2;
  5152             _len2Q = _len2-2;
  5153 	    while (_index < _len2Q) {
  5153             while (_index < _len2Q) {
  5154 		/* do not combine the expression below (may lead to unsigned result on some machines */
  5154                 /* do not combine the expression below (may lead to unsigned result on some machines */
  5155 		_diff = ((unsigned int *)(_myDigits+_index-1))[0];
  5155                 _diff = ((unsigned int *)(_myDigits+_index-1))[0];
  5156 		_diff -= ((unsigned int *)(_otherDigits+_index-1))[0];
  5156                 _diff -= ((unsigned int *)(_otherDigits+_index-1))[0];
  5157 		_diff -= _borrow;
  5157                 _diff -= _borrow;
  5158 		if (_diff >= 0) {
  5158                 if (_diff >= 0) {
  5159 		    _borrow = 0;
  5159                     _borrow = 0;
  5160 		} else {
  5160                 } else {
  5161 		    _borrow = 1;
  5161                     _borrow = 1;
  5162 		    /* _diff += 0x10000; */
  5162                     /* _diff += 0x10000; */
  5163 		}
  5163                 }
  5164 		((unsigned int *)(_myDigits+_index-1))[0] = _diff;
  5164                 ((unsigned int *)(_myDigits+_index-1))[0] = _diff;
  5165 		anyBitNonZero |= (_diff & 0xFFFFFFFFL);
  5165                 anyBitNonZero |= (_diff & 0xFFFFFFFFL);
  5166 		_index += 4;
  5166                 _index += 4;
  5167 	    }
  5167             }
  5168 	}
  5168         }
  5169 # endif
  5169 # endif
  5170 
  5170 
  5171 	/*
  5171         /*
  5172 	 * subtract short-wise
  5172          * subtract short-wise
  5173 	 */
  5173          */
  5174 	while (_index < _len2) {
  5174         while (_index < _len2) {
  5175 	    /* do not combine the expression below (may lead to unsigned result on some machines */
  5175             /* do not combine the expression below (may lead to unsigned result on some machines */
  5176 	    _diff = ((unsigned short *)(_myDigits+_index-1))[0];
  5176             _diff = ((unsigned short *)(_myDigits+_index-1))[0];
  5177 	    _diff -= ((unsigned short *)(_otherDigits+_index-1))[0];
  5177             _diff -= ((unsigned short *)(_otherDigits+_index-1))[0];
  5178 	    _diff -= _borrow;
  5178             _diff -= _borrow;
  5179 	    if (_diff >= 0) {
  5179             if (_diff >= 0) {
  5180 		_borrow = 0;
  5180                 _borrow = 0;
  5181 	    } else {
  5181             } else {
  5182 		_borrow = 1;
  5182                 _borrow = 1;
  5183 		/* _diff += 0x10000; */
  5183                 /* _diff += 0x10000; */
  5184 	    }
  5184             }
  5185 	    ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5185             ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5186 	    anyBitNonZero |= (_diff & 0xFFFF);
  5186             anyBitNonZero |= (_diff & 0xFFFF);
  5187 	    _index += 2;
  5187             _index += 2;
  5188 	}
  5188         }
  5189 
  5189 
  5190 	if (_index <= _len2) {
  5190         if (_index <= _len2) {
  5191 	    /*
  5191             /*
  5192 	     * cannot continue with shorts - there is an odd number of
  5192              * cannot continue with shorts - there is an odd number of
  5193 	     * bytes in the minuent
  5193              * bytes in the minuent
  5194 	     */
  5194              */
  5195 	} else {
  5195         } else {
  5196 	    while (_index < _len1) {
  5196             while (_index < _len1) {
  5197 		/* do not combine the expression below (may lead to unsigned result on some machines */
  5197                 /* do not combine the expression below (may lead to unsigned result on some machines */
  5198 		_diff = ((unsigned short *)(_myDigits+_index-1))[0];
  5198                 _diff = ((unsigned short *)(_myDigits+_index-1))[0];
  5199 		_diff -= _borrow;
  5199                 _diff -= _borrow;
  5200 		if (_diff >= 0) {
  5200                 if (_diff >= 0) {
  5201 		    /* _borrow = 0; */
  5201                     /* _borrow = 0; */
  5202 		    ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5202                     ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5203 		    anyBitNonZero |= (_diff & 0xFFFF);
  5203                     anyBitNonZero |= (_diff & 0xFFFF);
  5204 		    _index += 2;
  5204                     _index += 2;
  5205 		    while (_index < _len1) {
  5205                     while (_index < _len1) {
  5206 			anyBitNonZero |= ((unsigned short *)(_myDigits+_index-1))[0];
  5206                         anyBitNonZero |= ((unsigned short *)(_myDigits+_index-1))[0];
  5207 			if (anyBitNonZero) {
  5207                         if (anyBitNonZero) {
  5208 			    RETURN (true);
  5208                             RETURN (true);
  5209 			}
  5209                         }
  5210 			_index += 2;
  5210                         _index += 2;
  5211 		    }
  5211                     }
  5212 		    /* last odd index */
  5212                     /* last odd index */
  5213 		    if (_index <= _len1) {
  5213                     if (_index <= _len1) {
  5214 			anyBitNonZero |= _myDigits[_index - 1];;
  5214                         anyBitNonZero |= _myDigits[_index - 1];;
  5215 			if (anyBitNonZero) {
  5215                         if (anyBitNonZero) {
  5216 			    RETURN (true);
  5216                             RETURN (true);
  5217 			}
  5217                         }
  5218 			_index++;
  5218                         _index++;
  5219 		    }
  5219                     }
  5220 		    RETURN (anyBitNonZero ? true : false);
  5220                     RETURN (anyBitNonZero ? true : false);
  5221 		}
  5221                 }
  5222 		_borrow = 1;
  5222                 _borrow = 1;
  5223 		/* _diff += 0x10000; */
  5223                 /* _diff += 0x10000; */
  5224 
  5224 
  5225 		((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5225                 ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5226 		anyBitNonZero |= (_diff & 0xFFFF);
  5226                 anyBitNonZero |= (_diff & 0xFFFF);
  5227 		_index += 2;
  5227                 _index += 2;
  5228 	    }
  5228             }
  5229 	}
  5229         }
  5230 #endif
  5230 #endif
  5231 	/*
  5231         /*
  5232 	 * subtract byte-wise
  5232          * subtract byte-wise
  5233 	 */
  5233          */
  5234 	while (_index <= _len2) {
  5234         while (_index <= _len2) {
  5235 	    /* do not combine the expression below (may lead to unsigned result on some machines */
  5235             /* do not combine the expression below (may lead to unsigned result on some machines */
  5236 	    _diff = _myDigits[_index - 1];
  5236             _diff = _myDigits[_index - 1];
  5237 	    _diff -= _otherDigits[_index - 1];
  5237             _diff -= _otherDigits[_index - 1];
  5238 	    _diff -= _borrow;
  5238             _diff -= _borrow;
  5239 	    if (_diff >= 0) {
  5239             if (_diff >= 0) {
  5240 		_borrow = 0;
  5240                 _borrow = 0;
  5241 	    } else {
  5241             } else {
  5242 		_borrow = 1;
  5242                 _borrow = 1;
  5243 		/* _diff += 0x100; */
  5243                 /* _diff += 0x100; */
  5244 	    }
  5244             }
  5245 	    _myDigits[_index - 1] = _diff;
  5245             _myDigits[_index - 1] = _diff;
  5246 	    anyBitNonZero |= (_diff & 0xFF);
  5246             anyBitNonZero |= (_diff & 0xFF);
  5247 	    _index++;
  5247             _index++;
  5248 	}
  5248         }
  5249 
  5249 
  5250 	while (_index <= _len1) {
  5250         while (_index <= _len1) {
  5251 	    /* do not combine the expression below (may lead to unsigned result on some machines */
  5251             /* do not combine the expression below (may lead to unsigned result on some machines */
  5252 	    _diff = _myDigits[_index - 1];
  5252             _diff = _myDigits[_index - 1];
  5253 	    _diff -= _borrow;
  5253             _diff -= _borrow;
  5254 	    if (_diff >= 0) {
  5254             if (_diff >= 0) {
  5255 		/* _borrow = 0; */
  5255                 /* _borrow = 0; */
  5256 		_myDigits[_index - 1] = _diff;
  5256                 _myDigits[_index - 1] = _diff;
  5257 		anyBitNonZero |= (_diff & 0xFF);
  5257                 anyBitNonZero |= (_diff & 0xFF);
  5258 		_index++;
  5258                 _index++;
  5259 		while (_index <= _len1) {
  5259                 while (_index <= _len1) {
  5260 		    anyBitNonZero |= _myDigits[_index - 1];
  5260                     anyBitNonZero |= _myDigits[_index - 1];
  5261 		    if (anyBitNonZero) {
  5261                     if (anyBitNonZero) {
  5262 			RETURN (true);
  5262                         RETURN (true);
  5263 		    }
  5263                     }
  5264 		    _index++;
  5264                     _index++;
  5265 		}
  5265                 }
  5266 		break;
  5266                 break;
  5267 	    }
  5267             }
  5268 	    _borrow = 1;
  5268             _borrow = 1;
  5269 	    /* _diff += 0x100; */
  5269             /* _diff += 0x100; */
  5270 
  5270 
  5271 	    _myDigits[_index - 1] = _diff;
  5271             _myDigits[_index - 1] = _diff;
  5272 	    anyBitNonZero |= (_diff & 0xFF);
  5272             anyBitNonZero |= (_diff & 0xFF);
  5273 	    _index++;
  5273             _index++;
  5274 	}
  5274         }
  5275 	RETURN (anyBitNonZero ? true : false);
  5275         RETURN (anyBitNonZero ? true : false);
  5276     }
  5276     }
  5277 %}.
  5277 %}.
  5278 
  5278 
  5279     index := 1.
  5279     index := 1.
  5280     borrow := 0.
  5280     borrow := 0.
  5281 
  5281 
  5282     [index <= len1] whileTrue:[
  5282     [index <= len1] whileTrue:[
  5283 	diff := borrow.
  5283         diff := borrow.
  5284 	diff := diff + (digitByteArray basicAt:index).
  5284         diff := diff + (digitByteArray basicAt:index).
  5285 	index <= len2 ifTrue:[
  5285         index <= len2 ifTrue:[
  5286 	    diff := diff - (otherDigitByteArray basicAt:index).
  5286             diff := diff - (otherDigitByteArray basicAt:index).
  5287 	].
  5287         ].
  5288 
  5288 
  5289 	"/ workaround for
  5289         "/ workaround for
  5290 	"/ gcc code generator bug
  5290         "/ gcc code generator bug
  5291 
  5291 
  5292 	(diff >= 0) ifTrue:[
  5292         (diff >= 0) ifTrue:[
  5293 	    borrow := 0
  5293             borrow := 0
  5294 	] ifFalse:[
  5294         ] ifFalse:[
  5295 	    borrow := -1.
  5295             borrow := -1.
  5296 	    diff := diff + 16r100
  5296             diff := diff + 16r100
  5297 	].
  5297         ].
  5298 	diff ~~ 0 ifTrue:[
  5298         diff ~~ 0 ifTrue:[
  5299 	    notZero := true
  5299             notZero := true
  5300 	].
  5300         ].
  5301 	digitByteArray basicAt:index put:diff.
  5301         digitByteArray basicAt:index put:diff.
  5302 	index := index + 1
  5302         index := index + 1
  5303     ].
  5303     ].
  5304 
  5304 
  5305     ^ notZero
  5305     ^ notZero
  5306 
  5306 
  5307     "Created: / 5.11.1996 / 16:23:47 / cg"
  5307     "Created: / 5.11.1996 / 16:23:47 / cg"
  5318 
  5318 
  5319 %{  /* NOCONTEXT */
  5319 %{  /* NOCONTEXT */
  5320     OBJ __digits = __INST(digitByteArray);
  5320     OBJ __digits = __INST(digitByteArray);
  5321 
  5321 
  5322     if (__isByteArray(__digits)) {
  5322     if (__isByteArray(__digits)) {
  5323 	int __nBytes = __byteArraySize(__digits);
  5323         int __nBytes = __byteArraySize(__digits);
  5324 	unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
  5324         unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
  5325 	unsigned INT __this, __next;
  5325         unsigned INT __this, __next;
  5326 	int __idx;
  5326         int __idx;
  5327 
  5327 
  5328 	if (__nBytes == 1) {
  5328         if (__nBytes == 1) {
  5329 	    __bp[0] >>= 1;
  5329             __bp[0] >>= 1;
  5330 	    RETURN (self);
  5330             RETURN (self);
  5331 	}
  5331         }
  5332 
  5332 
  5333 	__idx = 1;
  5333         __idx = 1;
  5334 
  5334 
  5335 #if defined(__LSBFIRST__)
  5335 #if defined(__LSBFIRST__)
  5336 # if (__POINTER_SIZE__ == 8)
  5336 # if (__POINTER_SIZE__ == 8)
  5337 	if (sizeof(unsigned INT) == 8) {
  5337         if (sizeof(unsigned INT) == 8) {
  5338 	    int __endIndex = __nBytes - 8;
  5338             int __endIndex = __nBytes - 8;
  5339 
  5339 
  5340 	    if (__idx < __endIndex) {
  5340             if (__idx < __endIndex) {
  5341 		__this = ((unsigned INT *)__bp)[0];
  5341                 __this = ((unsigned INT *)__bp)[0];
  5342 
  5342 
  5343 		while (__idx < __endIndex) {
  5343                 while (__idx < __endIndex) {
  5344 		    __next = ((unsigned INT *)__bp)[1];
  5344                     __next = ((unsigned INT *)__bp)[1];
  5345 		    __this = (__this >> 1) /* & 0x7FFFFFFFFFFFFFF */;
  5345                     __this = (__this >> 1) /* & 0x7FFFFFFFFFFFFFF */;
  5346 		    __this |= __next << 63;
  5346                     __this |= __next << 63;
  5347 		    ((unsigned INT *)__bp)[0] = __this;
  5347                     ((unsigned INT *)__bp)[0] = __this;
  5348 		    __this = __next;
  5348                     __this = __next;
  5349 		    __bp += 8;
  5349                     __bp += 8;
  5350 		    __idx += 8;
  5350                     __idx += 8;
  5351 		}
  5351                 }
  5352 	    }
  5352             }
  5353 
  5353 
  5354 	    if (__idx < (__nBytes - 4)) {
  5354             if (__idx < (__nBytes - 4)) {
  5355 		__this = ((unsigned int *)__bp)[0];
  5355                 __this = ((unsigned int *)__bp)[0];
  5356 
  5356 
  5357 		__next = ((unsigned int *)__bp)[1];
  5357                 __next = ((unsigned int *)__bp)[1];
  5358 		__this = (__this >> 1) /* & 0x7FFFFFF */;
  5358                 __this = (__this >> 1) /* & 0x7FFFFFF */;
  5359 		__this |= __next << 31;
  5359                 __this |= __next << 31;
  5360 		((unsigned int *)__bp)[0] = __this;
  5360                 ((unsigned int *)__bp)[0] = __this;
  5361 		__this = __next;
  5361                 __this = __next;
  5362 		__bp += 4;
  5362                 __bp += 4;
  5363 		__idx += 4;
  5363                 __idx += 4;
  5364 	    }
  5364             }
  5365 	    if (__idx < (__nBytes - 2)) {
  5365             if (__idx < (__nBytes - 2)) {
  5366 		__this = ((unsigned short *)__bp)[0];
  5366                 __this = ((unsigned short *)__bp)[0];
  5367 
  5367 
  5368 		__next = ((unsigned short *)__bp)[1];
  5368                 __next = ((unsigned short *)__bp)[1];
  5369 		__this = (__this >> 1) /* & 0x7FFFFFF */;
  5369                 __this = (__this >> 1) /* & 0x7FFFFFF */;
  5370 		__this |= __next << 15;
  5370                 __this |= __next << 15;
  5371 		((unsigned short *)__bp)[0] = __this;
  5371                 ((unsigned short *)__bp)[0] = __this;
  5372 		__this = __next;
  5372                 __this = __next;
  5373 		__bp += 2;
  5373                 __bp += 2;
  5374 		__idx += 2;
  5374                 __idx += 2;
  5375 	    }
  5375             }
  5376 	}
  5376         }
  5377 # else
  5377 # else
  5378 	if (sizeof(unsigned int) == 4) {
  5378         if (sizeof(unsigned int) == 4) {
  5379 	    int __endIndex = __nBytes - 4;
  5379             int __endIndex = __nBytes - 4;
  5380 
  5380 
  5381 	    if (__idx < __endIndex) {
  5381             if (__idx < __endIndex) {
  5382 		__this = ((unsigned int *)__bp)[0];
  5382                 __this = ((unsigned int *)__bp)[0];
  5383 
  5383 
  5384 		while (__idx < __endIndex) {
  5384                 while (__idx < __endIndex) {
  5385 		    __next = ((unsigned int *)__bp)[1];
  5385                     __next = ((unsigned int *)__bp)[1];
  5386 		    __this = (__this >> 1) /* & 0x7FFFFFF */;
  5386                     __this = (__this >> 1) /* & 0x7FFFFFF */;
  5387 		    __this |= __next << 31;
  5387                     __this |= __next << 31;
  5388 		    ((unsigned int *)__bp)[0] = __this;
  5388                     ((unsigned int *)__bp)[0] = __this;
  5389 		    __this = __next;
  5389                     __this = __next;
  5390 		    __bp += 4;
  5390                     __bp += 4;
  5391 		    __idx += 4;
  5391                     __idx += 4;
  5392 		}
  5392                 }
  5393 	    }
  5393             }
  5394 	}
  5394         }
  5395 # endif
  5395 # endif
  5396 #endif
  5396 #endif
  5397 
  5397 
  5398 	__this = __bp[0];
  5398         __this = __bp[0];
  5399 	while (__idx < __nBytes) {
  5399         while (__idx < __nBytes) {
  5400 	    __next = __bp[1];
  5400             __next = __bp[1];
  5401 	    __this >>= 1;
  5401             __this >>= 1;
  5402 	    __this |= __next << 7;
  5402             __this |= __next << 7;
  5403 	    __bp[0] = __this;
  5403             __bp[0] = __this;
  5404 	    __this = __next;
  5404             __this = __next;
  5405 	    __bp++;
  5405             __bp++;
  5406 	    __idx++;
  5406             __idx++;
  5407 	}
  5407         }
  5408 	__bp[0] = __this >> 1;
  5408         __bp[0] = __this >> 1;
  5409 	RETURN (self);
  5409         RETURN (self);
  5410     }
  5410     }
  5411 %}.
  5411 %}.
  5412 
  5412 
  5413     prevBit := 0.
  5413     prevBit := 0.
  5414     digitByteArray size to:1 by:-1 do:[:idx |
  5414     digitByteArray size to:1 by:-1 do:[:idx |
  5415 	|thisByte|
  5415         |thisByte|
  5416 
  5416 
  5417 	thisByte := digitByteArray at:idx.
  5417         thisByte := digitByteArray at:idx.
  5418 	digitByteArray at:idx put:((thisByte bitShift:-1) bitOr:prevBit).
  5418         digitByteArray at:idx put:((thisByte bitShift:-1) bitOr:prevBit).
  5419 	prevBit := (thisByte bitAnd:1) bitShift:7.
  5419         prevBit := (thisByte bitAnd:1) bitShift:7.
  5420     ].
  5420     ].
  5421 
  5421 
  5422     "
  5422     "
  5423      100000 asLargeInteger div2
  5423      100000 asLargeInteger div2
  5424      1000000000000000000000000000 div2
  5424      1000000000000000000000000000 div2
  5438 
  5438 
  5439     nBytes := digitByteArray size.
  5439     nBytes := digitByteArray size.
  5440 
  5440 
  5441     b := digitByteArray at:nBytes.
  5441     b := digitByteArray at:nBytes.
  5442     (b bitAnd:16r80) ~~ 0 ifTrue:[
  5442     (b bitAnd:16r80) ~~ 0 ifTrue:[
  5443 	"/ need another byte
  5443         "/ need another byte
  5444 	nBytes := nBytes + 1.
  5444         nBytes := nBytes + 1.
  5445 	t := ByteArray uninitializedNew:nBytes.
  5445         t := ByteArray uninitializedNew:nBytes.
  5446 	t replaceFrom:1 to:nBytes-1 with:digitByteArray startingAt:1.
  5446         t replaceFrom:1 to:nBytes-1 with:digitByteArray startingAt:1.
  5447 	t at:nBytes put:0.
  5447         t at:nBytes put:0.
  5448 	digitByteArray := t.
  5448         digitByteArray := t.
  5449     ].
  5449     ].
  5450 
  5450 
  5451 %{
  5451 %{
  5452     OBJ __digits = __INST(digitByteArray);
  5452     OBJ __digits = __INST(digitByteArray);
  5453 
  5453 
  5454     if (__isByteArray(__digits)) {
  5454     if (__isByteArray(__digits)) {
  5455 	int __nBytes = __intVal(nBytes);
  5455         int __nBytes = __intVal(nBytes);
  5456 	unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
  5456         unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
  5457 	unsigned INT __carry = 0, __newCarry;
  5457         unsigned INT __carry = 0, __newCarry;
  5458 
  5458 
  5459 #if defined(__LSBFIRST__)
  5459 #if defined(__LSBFIRST__)
  5460 # if (__POINTER_SIZE__ == 8)
  5460 # if (__POINTER_SIZE__ == 8)
  5461 	if (sizeof(unsigned INT) == 8) {
  5461         if (sizeof(unsigned INT) == 8) {
  5462 	    while (__nBytes >= 8) {
  5462             while (__nBytes >= 8) {
  5463 		unsigned INT __this;
  5463                 unsigned INT __this;
  5464 
  5464 
  5465 		__this = ((unsigned INT *)__bp)[0];
  5465                 __this = ((unsigned INT *)__bp)[0];
  5466 		__newCarry = (__this >> 63) /* & 1 */;
  5466                 __newCarry = (__this >> 63) /* & 1 */;
  5467 		((unsigned INT *)__bp)[0] = (__this << 1) | __carry;
  5467                 ((unsigned INT *)__bp)[0] = (__this << 1) | __carry;
  5468 		__carry = __newCarry;
  5468                 __carry = __newCarry;
  5469 		__bp += 8;
  5469                 __bp += 8;
  5470 		__nBytes -= 8;
  5470                 __nBytes -= 8;
  5471 	    }
  5471             }
  5472 	}
  5472         }
  5473 # endif
  5473 # endif
  5474 	if (sizeof(unsigned int) == 4) {
  5474         if (sizeof(unsigned int) == 4) {
  5475 	    while (__nBytes >= 4) {
  5475             while (__nBytes >= 4) {
  5476 		unsigned int __this;
  5476                 unsigned int __this;
  5477 
  5477 
  5478 		__this = ((unsigned int *)__bp)[0];
  5478                 __this = ((unsigned int *)__bp)[0];
  5479 		__newCarry = (__this >> 31) /* & 1 */;
  5479                 __newCarry = (__this >> 31) /* & 1 */;
  5480 		((unsigned int *)__bp)[0] = (__this << 1) | __carry;
  5480                 ((unsigned int *)__bp)[0] = (__this << 1) | __carry;
  5481 		__carry = __newCarry;
  5481                 __carry = __newCarry;
  5482 		__bp += 4;
  5482                 __bp += 4;
  5483 		__nBytes -= 4;
  5483                 __nBytes -= 4;
  5484 	    }
  5484             }
  5485 	}
  5485         }
  5486 	if (__nBytes >= 2) {
  5486         if (__nBytes >= 2) {
  5487 	    unsigned short __this;
  5487             unsigned short __this;
  5488 
  5488 
  5489 	    __this = ((unsigned short *)__bp)[0];
  5489             __this = ((unsigned short *)__bp)[0];
  5490 	    __newCarry = (__this >> 15) /* & 1 */;
  5490             __newCarry = (__this >> 15) /* & 1 */;
  5491 	    ((unsigned short *)__bp)[0] = (__this << 1) | __carry;
  5491             ((unsigned short *)__bp)[0] = (__this << 1) | __carry;
  5492 	    __carry = __newCarry;
  5492             __carry = __newCarry;
  5493 	    __bp += 2;
  5493             __bp += 2;
  5494 	    __nBytes -= 2;
  5494             __nBytes -= 2;
  5495 	}
  5495         }
  5496 #endif /* LSBFIRST */
  5496 #endif /* LSBFIRST */
  5497 	while (__nBytes) {
  5497         while (__nBytes) {
  5498 	    unsigned char __this;
  5498             unsigned char __this;
  5499 
  5499 
  5500 	    __this = __bp[0];
  5500             __this = __bp[0];
  5501 	    __newCarry = (__this >> 7) /* & 1 */;
  5501             __newCarry = (__this >> 7) /* & 1 */;
  5502 	    __bp[0] = (__this << 1) | __carry;
  5502             __bp[0] = (__this << 1) | __carry;
  5503 	    __carry = __newCarry;
  5503             __carry = __newCarry;
  5504 	    __bp++;
  5504             __bp++;
  5505 	    __nBytes--;
  5505             __nBytes--;
  5506 	}
  5506         }
  5507 	RETURN (self);
  5507         RETURN (self);
  5508     }
  5508     }
  5509 %}.
  5509 %}.
  5510 
  5510 
  5511     prevBit := 0.
  5511     prevBit := 0.
  5512     1 to:digitByteArray size do:[:idx |
  5512     1 to:digitByteArray size do:[:idx |
  5513 	|thisByte|
  5513         |thisByte|
  5514 
  5514 
  5515 	thisByte := digitByteArray at:idx.
  5515         thisByte := digitByteArray at:idx.
  5516 	digitByteArray at:idx put:(((thisByte bitShift:1) bitAnd:16rFF) bitOr:prevBit).
  5516         digitByteArray at:idx put:(((thisByte bitShift:1) bitAnd:16rFF) bitOr:prevBit).
  5517 	prevBit := (thisByte bitShift:-7) bitAnd:1.
  5517         prevBit := (thisByte bitShift:-7) bitAnd:1.
  5518     ].
  5518     ].
  5519 
  5519 
  5520     "
  5520     "
  5521      100000 asLargeInteger mul2
  5521      100000 asLargeInteger mul2
  5522      16r7FFFFFFFFFFF copy mul2 hexPrintString
  5522      16r7FFFFFFFFFFF copy mul2 hexPrintString