LargeInteger.st
branchjv
changeset 19137 199b5e15b1da
parent 19127 940613fe6659
parent 19135 e2d82660b855
child 19158 cdce727939ab
equal deleted inserted replaced
19127:940613fe6659 19137:199b5e15b1da
     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     "
  1522 
  1522 
  1523 %{
  1523 %{
  1524     unsigned INT swapped;
  1524     unsigned INT swapped;
  1525 
  1525 
  1526     swapped = ( (__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[0]) << 24)
  1526     swapped = ( (__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[0]) << 24)
  1527 	      | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[1]) << 16)
  1527               | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[1]) << 16)
  1528 	      | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[2]) << 8)
  1528               | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[2]) << 8)
  1529 	      | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[3]));
  1529               | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[3]));
  1530     RETURN (__MKUINT(swapped));
  1530     RETURN (__MKUINT(swapped));
  1531 %}.
  1531 %}.
  1532 
  1532     ^ super byteSwapped32
  1533     "
  1533 
  1534      (LargeInteger value:16r11223344) byteSwapped hexPrintString
  1534     "
  1535      (LargeInteger value:16r44332211) byteSwapped hexPrintString
  1535      (LargeInteger value:16r11223344) byteSwapped32 hexPrintString
  1536      16r88776655 byteSwapped hexPrintString
  1536      (LargeInteger value:16r44332211) byteSwapped32 hexPrintString
  1537      16r11223344 byteSwapped hexPrintString
  1537      16r88776655 byteSwapped32 hexPrintString
       
  1538      16r11223344 byteSwapped32 hexPrintString
  1538     "
  1539     "
  1539 
  1540 
  1540     "Created: / 31-01-2012 / 11:07:42 / cg"
  1541     "Created: / 31-01-2012 / 11:07:42 / cg"
  1541 !
  1542 !
  1542 
  1543 
  1549     unsigned INT swappedLO = 0;
  1550     unsigned INT swappedLO = 0;
  1550     unsigned INT swappedHI;
  1551     unsigned INT swappedHI;
  1551     unsigned INT swapped;
  1552     unsigned INT swapped;
  1552 
  1553 
  1553     swappedHI = ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[0]) << 24)
  1554     swappedHI = ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[0]) << 24)
  1554 	      | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[1]) << 16)
  1555               | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[1]) << 16)
  1555 	      | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[2]) << 8)
  1556               | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[2]) << 8)
  1556 	      | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[3]));
  1557               | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[3]));
  1557     if (__byteArraySize(__INST(digitByteArray)) > 4) {
  1558     if (__byteArraySize(__INST(digitByteArray)) > 4) {
  1558 	swappedLO = ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[4]) << 24)
  1559         swappedLO = ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[4]) << 24)
  1559 		  | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[5]) << 16)
  1560                   | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[5]) << 16)
  1560 		  | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[6]) << 8)
  1561                   | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[6]) << 8)
  1561 		  | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[7]));
  1562                   | ((__ByteArrayInstPtr(__INST(digitByteArray))->ba_element[7]));
  1562     }
  1563     }
  1563 
  1564 
  1564 #if __POINTER_SIZE__ == 8
  1565 #if __POINTER_SIZE__ == 8
  1565     swapped = (swappedHI<<32) | swappedLO;
  1566     swapped = (swappedHI<<32) | swappedLO;
  1566     RETURN(__MKUINT( swapped ));
  1567     RETURN(__MKUINT( swapped ));
  1567 #else
  1568 #else
  1568     RETURN(__MKLARGEINT64(1, swappedLO, swappedHI));
  1569     RETURN(__MKLARGEINT64(1, swappedLO, swappedHI));
  1569 #endif
  1570 #endif
  1570 %}.
  1571 %}.
       
  1572     ^ super byteSwapped64
  1571 
  1573 
  1572     "
  1574     "
  1573      (LargeInteger value:16r11223344) byteSwapped64 hexPrintString
  1575      (LargeInteger value:16r11223344) byteSwapped64 hexPrintString
  1574      (LargeInteger value:16r44332211) byteSwapped64 hexPrintString
  1576      (LargeInteger value:16r44332211) byteSwapped64 hexPrintString
  1575      (LargeInteger value:16r1122334455667788) byteSwapped64 hexPrintString
  1577      (LargeInteger value:16r1122334455667788) byteSwapped64 hexPrintString
  1712     return context._RETURN( STInteger._new( ((STLargeInteger)self).digitLength() ));
  1714     return context._RETURN( STInteger._new( ((STLargeInteger)self).digitLength() ));
  1713 #endif
  1715 #endif
  1714 %}.
  1716 %}.
  1715     l := digitByteArray size.
  1717     l := digitByteArray size.
  1716     [l ~~ 0 and:[(digitByteArray at:l) == 0]] whileTrue:[
  1718     [l ~~ 0 and:[(digitByteArray at:l) == 0]] whileTrue:[
  1717 	l := l - 1.
  1719         l := l - 1.
  1718     ].
  1720     ].
  1719     ^ l
  1721     ^ l
  1720 
  1722 
  1721     "Modified: 31.7.1997 / 13:18:28 / cg"
  1723     "Modified: 31.7.1997 / 13:18:28 / cg"
  1722 !
  1724 !
  1814 
  1816 
  1815 %{  /* NOCONTEXT */
  1817 %{  /* NOCONTEXT */
  1816     OBJ t;
  1818     OBJ t;
  1817 
  1819 
  1818     if (__INST(sign) == __mkSmallInteger(0)) {
  1820     if (__INST(sign) == __mkSmallInteger(0)) {
  1819 	RETURN (__mkSmallInteger(0));
  1821         RETURN (__mkSmallInteger(0));
  1820     }
  1822     }
  1821 
  1823 
  1822     t = __INST(digitByteArray);
  1824     t = __INST(digitByteArray);
  1823     if (__isByteArray(t)) {
  1825     if (__isByteArray(t)) {
  1824 	unsigned char *__digitBytes = __ByteArrayInstPtr(t)->ba_element;
  1826         unsigned char *__digitBytes = __ByteArrayInstPtr(t)->ba_element;
  1825 	int _idx, _idx0;
  1827         int _idx, _idx0;
  1826 	INT _val;
  1828         INT _val;
  1827 
  1829 
  1828 	_idx = _idx0 = __byteArraySize(t);
  1830         _idx = _idx0 = __byteArraySize(t);
  1829 	while ((_idx > 0) && (__digitBytes[_idx - 1] == 0)) {
  1831         while ((_idx > 0) && (__digitBytes[_idx - 1] == 0)) {
  1830 	    _idx--;
  1832             _idx--;
  1831 	}
  1833         }
  1832 #if __POINTER_SIZE__ == 8
  1834 #if __POINTER_SIZE__ == 8
  1833 	switch (_idx) {
  1835         switch (_idx) {
  1834 	    case 8:
  1836             case 8:
  1835 		_val = __digitBytes[7];
  1837                 _val = __digitBytes[7];
  1836 		if (_val <= 0x40) {
  1838                 if (_val <= 0x40) {
  1837 		    _val = (_val<<8);
  1839                     _val = (_val<<8);
  1838 		    _val = (_val + __digitBytes[6]) << 8;
  1840                     _val = (_val + __digitBytes[6]) << 8;
  1839 		    _val = (_val + __digitBytes[5]) << 8;
  1841                     _val = (_val + __digitBytes[5]) << 8;
  1840 		    _val = (_val + __digitBytes[4]) << 8;
  1842                     _val = (_val + __digitBytes[4]) << 8;
  1841 		    _val = (_val + __digitBytes[3]) << 8;
  1843                     _val = (_val + __digitBytes[3]) << 8;
  1842 		    _val = (_val + __digitBytes[2]) << 8;
  1844                     _val = (_val + __digitBytes[2]) << 8;
  1843 		    _val = (_val + __digitBytes[1]) << 8;
  1845                     _val = (_val + __digitBytes[1]) << 8;
  1844 		    _val += __digitBytes[0];
  1846                     _val += __digitBytes[0];
  1845 		    if (__INST(sign) == __mkSmallInteger(-1))
  1847                     if (__INST(sign) == __mkSmallInteger(-1))
  1846 			_val = -_val;
  1848                         _val = -_val;
  1847 		    if (__ISVALIDINTEGER(_val)) {
  1849                     if (__ISVALIDINTEGER(_val)) {
  1848 			RETURN (__mkSmallInteger(_val));
  1850                         RETURN (__mkSmallInteger(_val));
  1849 		    }
  1851                     }
  1850 		}
  1852                 }
  1851 		break;
  1853                 break;
  1852 	    case 7:
  1854             case 7:
  1853 # if defined(__LSBFIRST__)
  1855 # if defined(__LSBFIRST__)
  1854 		_val = ((INT *)__digitBytes)[0] & 0x00FFFFFFFFFFFFFFL;
  1856                 _val = ((INT *)__digitBytes)[0] & 0x00FFFFFFFFFFFFFFL;
  1855 # else
  1857 # else
  1856 		_val = (__digitBytes[6]<<8);
  1858                 _val = (__digitBytes[6]<<8);
  1857 		_val = (_val + __digitBytes[5]) << 8;
  1859                 _val = (_val + __digitBytes[5]) << 8;
  1858 		_val = (_val + __digitBytes[4]) << 8;
  1860                 _val = (_val + __digitBytes[4]) << 8;
  1859 		_val = (_val + __digitBytes[3]) << 8;
  1861                 _val = (_val + __digitBytes[3]) << 8;
  1860 		_val = (_val + __digitBytes[2]) << 8;
  1862                 _val = (_val + __digitBytes[2]) << 8;
  1861 		_val = (_val + __digitBytes[1]) << 8;
  1863                 _val = (_val + __digitBytes[1]) << 8;
  1862 		_val += __digitBytes[0];
  1864                 _val += __digitBytes[0];
  1863 # endif
  1865 # endif
  1864 		if (__INST(sign) == __mkSmallInteger(-1))
  1866                 if (__INST(sign) == __mkSmallInteger(-1))
  1865 		    _val = -_val;
  1867                     _val = -_val;
  1866 		RETURN (__mkSmallInteger(_val));
  1868                 RETURN (__mkSmallInteger(_val));
  1867 	    case 6:
  1869             case 6:
  1868 # if defined(__LSBFIRST__)
  1870 # if defined(__LSBFIRST__)
  1869 		_val = ((INT *)__digitBytes)[0] & 0x0000FFFFFFFFFFFFL;
  1871                 _val = ((INT *)__digitBytes)[0] & 0x0000FFFFFFFFFFFFL;
  1870 # else
  1872 # else
  1871 		_val = (__digitBytes[5]<<8);
  1873                 _val = (__digitBytes[5]<<8);
  1872 		_val = (_val + __digitBytes[4]) << 8;
  1874                 _val = (_val + __digitBytes[4]) << 8;
  1873 		_val = (_val + __digitBytes[3]) << 8;
  1875                 _val = (_val + __digitBytes[3]) << 8;
  1874 		_val = (_val + __digitBytes[2]) << 8;
  1876                 _val = (_val + __digitBytes[2]) << 8;
  1875 		_val = (_val + __digitBytes[1]) << 8;
  1877                 _val = (_val + __digitBytes[1]) << 8;
  1876 		_val += __digitBytes[0];
  1878                 _val += __digitBytes[0];
  1877 # endif
  1879 # endif
  1878 		if (__INST(sign) == __mkSmallInteger(-1))
  1880                 if (__INST(sign) == __mkSmallInteger(-1))
  1879 		    _val = -_val;
  1881                     _val = -_val;
  1880 		RETURN (__mkSmallInteger(_val));
  1882                 RETURN (__mkSmallInteger(_val));
  1881 	    case 5:
  1883             case 5:
  1882 # if defined(__LSBFIRST__)
  1884 # if defined(__LSBFIRST__)
  1883 		_val = ((INT *)__digitBytes)[0] & 0x000000FFFFFFFFFFL;
  1885                 _val = ((INT *)__digitBytes)[0] & 0x000000FFFFFFFFFFL;
  1884 # else
  1886 # else
  1885 		_val = (__digitBytes[4]<<8);
  1887                 _val = (__digitBytes[4]<<8);
  1886 		_val = (_val + __digitBytes[3]) << 8;
  1888                 _val = (_val + __digitBytes[3]) << 8;
  1887 		_val = (_val + __digitBytes[2]) << 8;
  1889                 _val = (_val + __digitBytes[2]) << 8;
  1888 		_val = (_val + __digitBytes[1]) << 8;
  1890                 _val = (_val + __digitBytes[1]) << 8;
  1889 		_val += __digitBytes[0];
  1891                 _val += __digitBytes[0];
  1890 # endif
  1892 # endif
  1891 		if (__INST(sign) == __mkSmallInteger(-1))
  1893                 if (__INST(sign) == __mkSmallInteger(-1))
  1892 		    _val = -_val;
  1894                     _val = -_val;
  1893 		RETURN (__mkSmallInteger(_val));
  1895                 RETURN (__mkSmallInteger(_val));
  1894 	    case 4:
  1896             case 4:
  1895 # if defined(__LSBFIRST__)
  1897 # if defined(__LSBFIRST__)
  1896 		_val = ((INT *)__digitBytes)[0] & 0x00000000FFFFFFFFL;
  1898                 _val = ((INT *)__digitBytes)[0] & 0x00000000FFFFFFFFL;
  1897 # else
  1899 # else
  1898 		_val = (__digitBytes[3]<<8);
  1900                 _val = (__digitBytes[3]<<8);
  1899 		_val = (_val + __digitBytes[2]) << 8;
  1901                 _val = (_val + __digitBytes[2]) << 8;
  1900 		_val = (_val + __digitBytes[1]) << 8;
  1902                 _val = (_val + __digitBytes[1]) << 8;
  1901 		_val += __digitBytes[0];
  1903                 _val += __digitBytes[0];
  1902 # endif
  1904 # endif
  1903 		if (__INST(sign) == __mkSmallInteger(-1))
  1905                 if (__INST(sign) == __mkSmallInteger(-1))
  1904 		    _val = -_val;
  1906                     _val = -_val;
  1905 		RETURN (__mkSmallInteger(_val));
  1907                 RETURN (__mkSmallInteger(_val));
  1906 	    case 3:
  1908             case 3:
  1907 # if defined(__LSBFIRST__)
  1909 # if defined(__LSBFIRST__)
  1908 		_val = ((int *)__digitBytes)[0] & 0x00FFFFFF;
  1910                 _val = ((int *)__digitBytes)[0] & 0x00FFFFFF;
  1909 # else
  1911 # else
  1910 		_val = (__digitBytes[2]<<8);
  1912                 _val = (__digitBytes[2]<<8);
  1911 		_val = (_val + __digitBytes[1]) << 8;
  1913                 _val = (_val + __digitBytes[1]) << 8;
  1912 		_val += __digitBytes[0];
  1914                 _val += __digitBytes[0];
  1913 # endif
  1915 # endif
  1914 		if (__INST(sign) == __mkSmallInteger(-1))
  1916                 if (__INST(sign) == __mkSmallInteger(-1))
  1915 		    _val = -_val;
  1917                     _val = -_val;
  1916 		RETURN (__mkSmallInteger(_val));
  1918                 RETURN (__mkSmallInteger(_val));
  1917 	    case 2:
  1919             case 2:
  1918 # if defined(__LSBFIRST__)
  1920 # if defined(__LSBFIRST__)
  1919 		_val = ((int *)__digitBytes)[0] & 0x0000FFFF;
  1921                 _val = ((int *)__digitBytes)[0] & 0x0000FFFF;
  1920 # else
  1922 # else
  1921 		_val = (__digitBytes[1]<<8) + __digitBytes[0];
  1923                 _val = (__digitBytes[1]<<8) + __digitBytes[0];
  1922 # endif
  1924 # endif
  1923 		if (__INST(sign) == __mkSmallInteger(-1))
  1925                 if (__INST(sign) == __mkSmallInteger(-1))
  1924 		    _val = -_val;
  1926                     _val = -_val;
  1925 		RETURN (__mkSmallInteger(_val));
  1927                 RETURN (__mkSmallInteger(_val));
  1926 	    case 1:
  1928             case 1:
  1927 		_val = __digitBytes[0];
  1929                 _val = __digitBytes[0];
  1928 		if (__INST(sign) == __mkSmallInteger(-1))
  1930                 if (__INST(sign) == __mkSmallInteger(-1))
  1929 		    _val = -_val;
  1931                     _val = -_val;
  1930 		RETURN (__mkSmallInteger(_val));
  1932                 RETURN (__mkSmallInteger(_val));
  1931 	    case 0:
  1933             case 0:
  1932 		RETURN (__mkSmallInteger(0));
  1934                 RETURN (__mkSmallInteger(0));
  1933 
  1935 
  1934 	}
  1936         }
  1935 #else
  1937 #else
  1936 	if (_idx <= 4) {
  1938         if (_idx <= 4) {
  1937 	    if (_idx <= 2) {
  1939             if (_idx <= 2) {
  1938 		if (_idx == 0) {
  1940                 if (_idx == 0) {
  1939 		    RETURN (__mkSmallInteger(0));
  1941                     RETURN (__mkSmallInteger(0));
  1940 		}
  1942                 }
  1941 		if (_idx == 1) {
  1943                 if (_idx == 1) {
  1942 		    _val = __digitBytes[0];
  1944                     _val = __digitBytes[0];
  1943 		    if (__INST(sign) == __mkSmallInteger(-1))
  1945                     if (__INST(sign) == __mkSmallInteger(-1))
  1944 			_val = -_val;
  1946                         _val = -_val;
  1945 		    RETURN (__mkSmallInteger(_val));
  1947                     RETURN (__mkSmallInteger(_val));
  1946 		}
  1948                 }
  1947 # if defined(__LSBFIRST__)
  1949 # if defined(__LSBFIRST__)
  1948 		_val = ((int *)__digitBytes)[0] & 0x0000FFFF;
  1950                 _val = ((int *)__digitBytes)[0] & 0x0000FFFF;
  1949 # else
  1951 # else
  1950 		_val = (__digitBytes[1]<<8) + __digitBytes[0];
  1952                 _val = (__digitBytes[1]<<8) + __digitBytes[0];
  1951 # endif
  1953 # endif
  1952 		if (__INST(sign) == __mkSmallInteger(-1))
  1954                 if (__INST(sign) == __mkSmallInteger(-1))
  1953 		    _val = -_val;
  1955                     _val = -_val;
  1954 		RETURN (__mkSmallInteger(_val));
  1956                 RETURN (__mkSmallInteger(_val));
  1955 	    }
  1957             }
  1956 	    if (_idx == 3) {
  1958             if (_idx == 3) {
  1957 # if defined(__LSBFIRST__)
  1959 # if defined(__LSBFIRST__)
  1958 		_val = ((int *)__digitBytes)[0] & 0x00FFFFFF;
  1960                 _val = ((int *)__digitBytes)[0] & 0x00FFFFFF;
  1959 # else
  1961 # else
  1960 		_val = (((__digitBytes[2]<<8) + __digitBytes[1])<<8) + __digitBytes[0];
  1962                 _val = (((__digitBytes[2]<<8) + __digitBytes[1])<<8) + __digitBytes[0];
  1961 # endif
  1963 # endif
  1962 		if (__INST(sign) == __mkSmallInteger(-1))
  1964                 if (__INST(sign) == __mkSmallInteger(-1))
  1963 		    _val = -_val;
  1965                     _val = -_val;
  1964 		RETURN (__mkSmallInteger(_val));
  1966                 RETURN (__mkSmallInteger(_val));
  1965 	    }
  1967             }
  1966 	    _val = __digitBytes[3];
  1968             _val = __digitBytes[3];
  1967 	    if (_val <= 0x40) {
  1969             if (_val <= 0x40) {
  1968 # if defined(__LSBFIRST__)
  1970 # if defined(__LSBFIRST__)
  1969 		_val = ((int *)__digitBytes)[0];
  1971                 _val = ((int *)__digitBytes)[0];
  1970 # else
  1972 # else
  1971 		_val = (((((_val<<8) + __digitBytes[2])<<8) + __digitBytes[1])<<8) + __digitBytes[0];
  1973                 _val = (((((_val<<8) + __digitBytes[2])<<8) + __digitBytes[1])<<8) + __digitBytes[0];
  1972 # endif
  1974 # endif
  1973 		if (__INST(sign) == __mkSmallInteger(-1))
  1975                 if (__INST(sign) == __mkSmallInteger(-1))
  1974 		    _val = -_val;
  1976                     _val = -_val;
  1975 		if (__ISVALIDINTEGER(_val)) {
  1977                 if (__ISVALIDINTEGER(_val)) {
  1976 		    RETURN (__mkSmallInteger(_val));
  1978                     RETURN (__mkSmallInteger(_val));
  1977 		}
  1979                 }
  1978 	    }
  1980             }
  1979 	}
  1981         }
  1980 #endif
  1982 #endif
  1981 
  1983 
  1982 	if (_idx == _idx0) {
  1984         if (_idx == _idx0) {
  1983 	    RETURN (self);
  1985             RETURN (self);
  1984 	}
  1986         }
  1985 
  1987 
  1986 	/*
  1988         /*
  1987 	 * must copy & cut off some (zero)bytes
  1989          * must copy & cut off some (zero)bytes
  1988 	 */
  1990          */
  1989 	{
  1991         {
  1990 	    OBJ newDigits;
  1992             OBJ newDigits;
  1991 	    OBJ oldDigits;
  1993             OBJ oldDigits;
  1992 
  1994 
  1993 	    /*
  1995             /*
  1994 	     * careful - there is no context here to protect
  1996              * careful - there is no context here to protect
  1995 	     * the receiver ...
  1997              * the receiver ...
  1996 	     */
  1998              */
  1997 	    __PROTECT__(self);
  1999             __PROTECT__(self);
  1998 	    __PROTECT__(__INST(digitByteArray));
  2000             __PROTECT__(__INST(digitByteArray));
  1999 	    newDigits = __BYTEARRAY_UNINITIALIZED_NEW_INT(_idx);
  2001             newDigits = __BYTEARRAY_UNINITIALIZED_NEW_INT(_idx);
  2000 	    __UNPROTECT__(oldDigits);
  2002             __UNPROTECT__(oldDigits);
  2001 	    __UNPROTECT__(self);
  2003             __UNPROTECT__(self);
  2002 	    if (newDigits) {
  2004             if (newDigits) {
  2003 		bcopy(__ByteArrayInstPtr(oldDigits)->ba_element,
  2005                 bcopy(__ByteArrayInstPtr(oldDigits)->ba_element,
  2004 		      __ByteArrayInstPtr(newDigits)->ba_element,
  2006                       __ByteArrayInstPtr(newDigits)->ba_element,
  2005 		      _idx);
  2007                       _idx);
  2006 		__INST(digitByteArray) = newDigits; __STORE(self, newDigits);
  2008                 __INST(digitByteArray) = newDigits; __STORE(self, newDigits);
  2007 		RETURN (self);
  2009                 RETURN (self);
  2008 	    }
  2010             }
  2009 	    /*
  2011             /*
  2010 	     * allocation failed ...
  2012              * allocation failed ...
  2011 	     * ... fall through to trigger the error
  2013              * ... fall through to trigger the error
  2012 	     */
  2014              */
  2013 	}
  2015         }
  2014     }
  2016     }
  2015 %}.
  2017 %}.
  2016     index0 := index := digitByteArray size.
  2018     index0 := index := digitByteArray size.
  2017     [(index > 0) and:[(digitByteArray at:index) == 0]] whileTrue:[
  2019     [(index > 0) and:[(digitByteArray at:index) == 0]] whileTrue:[
  2018 	index := index - 1
  2020         index := index - 1
  2019     ].
  2021     ].
  2020 "/    ((index < SmallInteger maxBytes)
  2022 "/    ((index < SmallInteger maxBytes)
  2021 "/    or:[(index == SmallInteger maxBytes)
  2023 "/    or:[(index == SmallInteger maxBytes)
  2022 "/            and:[(digitByteArray at:index) < 16r20]])
  2024 "/            and:[(digitByteArray at:index) < 16r20]])
  2023 "/    ifTrue:[
  2025 "/    ifTrue:[
  2027 "/            val := val bitOr:(digitByteArray at:i).
  2029 "/            val := val bitOr:(digitByteArray at:i).
  2028 "/        ].
  2030 "/        ].
  2029 "/        ^ val * sign
  2031 "/        ^ val * sign
  2030 "/    ].
  2032 "/    ].
  2031     (index ~~ index0) ifTrue:[
  2033     (index ~~ index0) ifTrue:[
  2032 	digitByteArray := digitByteArray copyFrom:1 to:index
  2034         digitByteArray := digitByteArray copyFrom:1 to:index
  2033     ].
  2035     ].
  2034     ^ self
  2036     ^ self
  2035 !
  2037 !
  2036 
  2038 
  2037 generality
  2039 generality
  2068      could have simply created a 4-byte largeinteger and normalize it.
  2070      could have simply created a 4-byte largeinteger and normalize it.
  2069      The code below does the normalize right away, avoiding the
  2071      The code below does the normalize right away, avoiding the
  2070      overhead of producing any intermediate byte-arrays (and the scanning)
  2072      overhead of producing any intermediate byte-arrays (and the scanning)
  2071     "
  2073     "
  2072     (aSmallInteger == 0) ifTrue: [
  2074     (aSmallInteger == 0) ifTrue: [
  2073 	digitByteArray := ByteArray with:0.
  2075         digitByteArray := ByteArray with:0.
  2074 	sign := 0.
  2076         sign := 0.
  2075 	^ self
  2077         ^ self
  2076     ].
  2078     ].
  2077 
  2079 
  2078     (aSmallInteger < 0) ifTrue: [
  2080     (aSmallInteger < 0) ifTrue: [
  2079 	sign := -1.
  2081         sign := -1.
  2080 	absValue := aSmallInteger negated
  2082         absValue := aSmallInteger negated
  2081     ] ifFalse: [
  2083     ] ifFalse: [
  2082 	sign := 1.
  2084         sign := 1.
  2083 	absValue := aSmallInteger
  2085         absValue := aSmallInteger
  2084     ].
  2086     ].
  2085 
  2087 
  2086     b1 := absValue bitAnd:16rFF.
  2088     b1 := absValue bitAnd:16rFF.
  2087     absValue := absValue bitShift:-8.
  2089     absValue := absValue bitShift:-8.
  2088     absValue == 0 ifTrue:[
  2090     absValue == 0 ifTrue:[
  2089 	digitByteArray := ByteArray with:b1
  2091         digitByteArray := ByteArray with:b1
  2090     ] ifFalse:[
  2092     ] ifFalse:[
  2091 	b2 := absValue bitAnd:16rFF.
  2093         b2 := absValue bitAnd:16rFF.
  2092 	absValue := absValue bitShift:-8.
  2094         absValue := absValue bitShift:-8.
  2093 	absValue == 0 ifTrue:[
  2095         absValue == 0 ifTrue:[
  2094 	    digitByteArray := ByteArray with:b1 with:b2
  2096             digitByteArray := ByteArray with:b1 with:b2
  2095 	] ifFalse:[
  2097         ] ifFalse:[
  2096 	    b3 := absValue bitAnd:16rFF.
  2098             b3 := absValue bitAnd:16rFF.
  2097 	    absValue := absValue bitShift:-8.
  2099             absValue := absValue bitShift:-8.
  2098 	    absValue == 0 ifTrue:[
  2100             absValue == 0 ifTrue:[
  2099 		digitByteArray := ByteArray with:b1 with:b2 with:b3
  2101                 digitByteArray := ByteArray with:b1 with:b2 with:b3
  2100 	    ] ifFalse:[
  2102             ] ifFalse:[
  2101 		b4 := absValue bitAnd:16rFF.
  2103                 b4 := absValue bitAnd:16rFF.
  2102 		absValue := absValue bitShift:-8.
  2104                 absValue := absValue bitShift:-8.
  2103 		absValue == 0 ifTrue:[
  2105                 absValue == 0 ifTrue:[
  2104 		    digitByteArray := ByteArray with:b1 with:b2 with:b3 with:b4
  2106                     digitByteArray := ByteArray with:b1 with:b2 with:b3 with:b4
  2105 		] ifFalse:[
  2107                 ] ifFalse:[
  2106 		    b5 := absValue bitAnd:16rFF.
  2108                     b5 := absValue bitAnd:16rFF.
  2107 		    absValue := absValue bitShift:-8.
  2109                     absValue := absValue bitShift:-8.
  2108 		    absValue == 0 ifTrue:[
  2110                     absValue == 0 ifTrue:[
  2109 			digitByteArray := ByteArray new:5.
  2111                         digitByteArray := ByteArray new:5.
  2110 			digitByteArray at:1 put:b1.
  2112                         digitByteArray at:1 put:b1.
  2111 			digitByteArray at:2 put:b2.
  2113                         digitByteArray at:2 put:b2.
  2112 			digitByteArray at:3 put:b3.
  2114                         digitByteArray at:3 put:b3.
  2113 			digitByteArray at:4 put:b4.
  2115                         digitByteArray at:4 put:b4.
  2114 			digitByteArray at:5 put:b5.
  2116                         digitByteArray at:5 put:b5.
  2115 		    ] ifFalse:[
  2117                     ] ifFalse:[
  2116 			b6 := absValue bitAnd:16rFF.
  2118                         b6 := absValue bitAnd:16rFF.
  2117 			absValue := absValue bitShift:-8.
  2119                         absValue := absValue bitShift:-8.
  2118 			absValue == 0 ifTrue:[
  2120                         absValue == 0 ifTrue:[
  2119 			    digitByteArray := ByteArray new:6.
  2121                             digitByteArray := ByteArray new:6.
  2120 			    digitByteArray at:1 put:b1.
  2122                             digitByteArray at:1 put:b1.
  2121 			    digitByteArray at:2 put:b2.
  2123                             digitByteArray at:2 put:b2.
  2122 			    digitByteArray at:3 put:b3.
  2124                             digitByteArray at:3 put:b3.
  2123 			    digitByteArray at:4 put:b4.
  2125                             digitByteArray at:4 put:b4.
  2124 			    digitByteArray at:5 put:b5.
  2126                             digitByteArray at:5 put:b5.
  2125 			    digitByteArray at:6 put:b6.
  2127                             digitByteArray at:6 put:b6.
  2126 			] ifFalse:[
  2128                         ] ifFalse:[
  2127 			    b7 := absValue bitAnd:16rFF.
  2129                             b7 := absValue bitAnd:16rFF.
  2128 			    absValue := absValue bitShift:-8.
  2130                             absValue := absValue bitShift:-8.
  2129 			    absValue == 0 ifTrue:[
  2131                             absValue == 0 ifTrue:[
  2130 				digitByteArray := ByteArray new:7.
  2132                                 digitByteArray := ByteArray new:7.
  2131 				digitByteArray at:1 put:b1.
  2133                                 digitByteArray at:1 put:b1.
  2132 				digitByteArray at:2 put:b2.
  2134                                 digitByteArray at:2 put:b2.
  2133 				digitByteArray at:3 put:b3.
  2135                                 digitByteArray at:3 put:b3.
  2134 				digitByteArray at:4 put:b4.
  2136                                 digitByteArray at:4 put:b4.
  2135 				digitByteArray at:5 put:b5.
  2137                                 digitByteArray at:5 put:b5.
  2136 				digitByteArray at:6 put:b6.
  2138                                 digitByteArray at:6 put:b6.
  2137 				digitByteArray at:7 put:b7.
  2139                                 digitByteArray at:7 put:b7.
  2138 			    ] ifFalse:[
  2140                             ] ifFalse:[
  2139 				digitByteArray := ByteArray new:8.
  2141                                 digitByteArray := ByteArray new:8.
  2140 				digitByteArray at:1 put:b1.
  2142                                 digitByteArray at:1 put:b1.
  2141 				digitByteArray at:2 put:b2.
  2143                                 digitByteArray at:2 put:b2.
  2142 				digitByteArray at:3 put:b3.
  2144                                 digitByteArray at:3 put:b3.
  2143 				digitByteArray at:4 put:b4.
  2145                                 digitByteArray at:4 put:b4.
  2144 				digitByteArray at:5 put:b5.
  2146                                 digitByteArray at:5 put:b5.
  2145 				digitByteArray at:6 put:b6.
  2147                                 digitByteArray at:6 put:b6.
  2146 				digitByteArray at:7 put:b7.
  2148                                 digitByteArray at:7 put:b7.
  2147 				digitByteArray at:8 put:absValue.
  2149                                 digitByteArray at:8 put:absValue.
  2148 			    ]
  2150                             ]
  2149 			]
  2151                         ]
  2150 		    ]
  2152                     ]
  2151 		]
  2153                 ]
  2152 	    ]
  2154             ]
  2153 	]
  2155         ]
  2154     ]
  2156     ]
  2155 
  2157 
  2156     "Modified: / 26.5.1999 / 22:18:14 / cg"
  2158     "Modified: / 26.5.1999 / 22:18:14 / cg"
  2157 ! !
  2159 ! !
  2158 
  2160 
  2162     "return true, if the argument, aNumber is greater than the receiver"
  2164     "return true, if the argument, aNumber is greater than the receiver"
  2163 
  2165 
  2164     |otherSign|
  2166     |otherSign|
  2165 
  2167 
  2166     (aNumber class == self class) ifTrue:[
  2168     (aNumber class == self class) ifTrue:[
  2167 	otherSign := aNumber sign.
  2169         otherSign := aNumber sign.
  2168 
  2170 
  2169 	(sign > 0) ifTrue:[
  2171         (sign > 0) ifTrue:[
  2170 	    "I am positive"
  2172             "I am positive"
  2171 	    (otherSign > 0) ifTrue:[^ self absLess:aNumber].
  2173             (otherSign > 0) ifTrue:[^ self absLess:aNumber].
  2172 	    ^ false "aNumber is <= 0"
  2174             ^ false "aNumber is <= 0"
  2173 	].
  2175         ].
  2174 	"I am negative"
  2176         "I am negative"
  2175 	(otherSign > 0) ifTrue:[^ true].
  2177         (otherSign > 0) ifTrue:[^ true].
  2176 	(otherSign == 0) ifTrue:[^ true].
  2178         (otherSign == 0) ifTrue:[^ true].
  2177 	^ (aNumber absLess:self)
  2179         ^ (aNumber absLess:self)
  2178     ].
  2180     ].
  2179     (aNumber class == SmallInteger) ifTrue:[
  2181     (aNumber class == SmallInteger) ifTrue:[
  2180 	otherSign := aNumber sign.
  2182         otherSign := aNumber sign.
  2181 
  2183 
  2182 	(sign > 0) ifTrue:[
  2184         (sign > 0) ifTrue:[
  2183 	    "I am positive"
  2185             "I am positive"
  2184 	    ^ false "aNumber is <= 0"
  2186             ^ false "aNumber is <= 0"
  2185 	].
  2187         ].
  2186 	(sign == 0) ifTrue:[
  2188         (sign == 0) ifTrue:[
  2187 	    (otherSign > 0) ifTrue:[^ true].
  2189             (otherSign > 0) ifTrue:[^ true].
  2188 	    ^ false
  2190             ^ false
  2189 	].
  2191         ].
  2190 	"I am negative"
  2192         "I am negative"
  2191 	^ true
  2193         ^ true
  2192     ].
  2194     ].
  2193     "/ hack for epsilon tests
  2195     "/ hack for epsilon tests
  2194     (aNumber class == Float) ifTrue:[
  2196     (aNumber class == Float) ifTrue:[
  2195 	self negative ifTrue:[
  2197         self negative ifTrue:[
  2196 	    "/ 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
  2197 	    aNumber >= SmallInteger minVal asFloat ifTrue:[^ true].
  2199             aNumber >= SmallInteger minVal asFloat ifTrue:[^ true].
  2198 	] ifFalse:[
  2200         ] ifFalse:[
  2199 	    "/ 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
  2200 	    aNumber <= SmallInteger maxVal asFloat ifTrue:[^ false].
  2202             aNumber <= SmallInteger maxVal asFloat ifTrue:[^ false].
  2201 	].
  2203         ].
  2202     ].
  2204     ].
  2203 
  2205 
  2204     ^ aNumber lessFromInteger:self
  2206     ^ aNumber lessFromInteger:self
  2205 
  2207 
  2206     "Modified: / 31.7.2002 / 10:08:19 / cg"
  2208     "Modified: / 31.7.2002 / 10:08:19 / cg"
  2211      as the receiver, false otherwise"
  2213      as the receiver, false otherwise"
  2212 
  2214 
  2213     "/ speed up compare to 0
  2215     "/ speed up compare to 0
  2214 
  2216 
  2215     (aNumber == 0) ifTrue:[
  2217     (aNumber == 0) ifTrue:[
  2216 	^ sign == 0
  2218         ^ sign == 0
  2217     ].
  2219     ].
  2218 
  2220 
  2219     (aNumber class == self class) ifFalse:[
  2221     (aNumber class == self class) ifFalse:[
  2220 	"/
  2222         "/
  2221 	"/ here, we depend on the fact, that largeinteger
  2223         "/ here, we depend on the fact, that largeinteger
  2222 	"/ results are always converted to smallInts, if possible.
  2224         "/ results are always converted to smallInts, if possible.
  2223 	"/ therefore, a largeInt in the smallInt range is not allowed (possible)
  2225         "/ therefore, a largeInt in the smallInt range is not allowed (possible)
  2224 	"/
  2226         "/
  2225 	aNumber class == SmallInteger ifTrue:[^ false ].
  2227         aNumber class == SmallInteger ifTrue:[^ false ].
  2226 	^ aNumber equalFromInteger:self
  2228         ^ aNumber equalFromInteger:self
  2227     ].
  2229     ].
  2228 
  2230 
  2229     (aNumber sign == sign) ifFalse:[^ false].
  2231     (aNumber sign == sign) ifFalse:[^ false].
  2230     ^ digitByteArray = aNumber digitBytes "/ ^ self absEq:aNumber
  2232     ^ digitByteArray = aNumber digitBytes "/ ^ self absEq:aNumber
  2231 
  2233 
  2236     "return true, if the argument, aNumber is less than the receiver"
  2238     "return true, if the argument, aNumber is less than the receiver"
  2237 
  2239 
  2238     |otherSign|
  2240     |otherSign|
  2239 
  2241 
  2240     (aNumber class == self class) ifFalse:[
  2242     (aNumber class == self class) ifFalse:[
  2241 	^ (aNumber < self)
  2243         ^ (aNumber < self)
  2242     ].
  2244     ].
  2243     otherSign := aNumber sign.
  2245     otherSign := aNumber sign.
  2244 
  2246 
  2245     (sign > 0) ifTrue:[
  2247     (sign > 0) ifTrue:[
  2246 	"I am positive"
  2248         "I am positive"
  2247 	(otherSign > 0) ifTrue:[^ aNumber absLess:self].
  2249         (otherSign > 0) ifTrue:[^ aNumber absLess:self].
  2248 	^ true "aNumber is <= 0"
  2250         ^ true "aNumber is <= 0"
  2249     ].
  2251     ].
  2250     (sign == 0) ifTrue:[
  2252     (sign == 0) ifTrue:[
  2251 	"I am zero"
  2253         "I am zero"
  2252 	(otherSign > 0) ifTrue:[^ false].
  2254         (otherSign > 0) ifTrue:[^ false].
  2253 	^ true
  2255         ^ true
  2254     ].
  2256     ].
  2255     "I am negative"
  2257     "I am negative"
  2256     (otherSign > 0) ifTrue:[^ false].
  2258     (otherSign > 0) ifTrue:[^ false].
  2257     (otherSign == 0) ifTrue:[^ false].
  2259     (otherSign == 0) ifTrue:[^ false].
  2258     ^ (self absLess:aNumber)
  2260     ^ (self absLess:aNumber)
  2267 
  2269 
  2268     h := self bitAnd:16r3FFFFFFF.
  2270     h := self bitAnd:16r3FFFFFFF.
  2269 
  2271 
  2270     l := digitByteArray size.
  2272     l := digitByteArray size.
  2271     l >= 8 ifTrue:[
  2273     l >= 8 ifTrue:[
  2272 	h := h bitXor:(digitByteArray at:l).
  2274         h := h bitXor:(digitByteArray at:l).
  2273 	h := h bitXor:((digitByteArray at:l-1) bitShift:8).
  2275         h := h bitXor:((digitByteArray at:l-1) bitShift:8).
  2274 	h := h bitXor:((digitByteArray at:l-2) bitShift:16).
  2276         h := h bitXor:((digitByteArray at:l-2) bitShift:16).
  2275 	h := h bitXor:((digitByteArray at:l-3) bitShift:22).
  2277         h := h bitXor:((digitByteArray at:l-3) bitShift:22).
  2276 	l >= 12 ifTrue:[
  2278         l >= 12 ifTrue:[
  2277 	    m := l // 2.
  2279             m := l // 2.
  2278 	    h := h bitXor:(digitByteArray at:m-1).
  2280             h := h bitXor:(digitByteArray at:m-1).
  2279 	    h := h bitXor:((digitByteArray at:m) bitShift:8).
  2281             h := h bitXor:((digitByteArray at:m) bitShift:8).
  2280 	    h := h bitXor:((digitByteArray at:m+1) bitShift:16).
  2282             h := h bitXor:((digitByteArray at:m+1) bitShift:16).
  2281 	    h := h bitXor:((digitByteArray at:m+2) bitShift:22).
  2283             h := h bitXor:((digitByteArray at:m+2) bitShift:22).
  2282 	].
  2284         ].
  2283 	^ h
  2285         ^ h
  2284     ].
  2286     ].
  2285     ^ (h bitShift:3) + l
  2287     ^ (h bitShift:3) + l
  2286 
  2288 
  2287     "
  2289     "
  2288      16r80000000 hash
  2290      16r80000000 hash
  2303 differenceFromInteger:anInteger
  2305 differenceFromInteger:anInteger
  2304     "sent, when anInteger does not know how to subtract the receiver.
  2306     "sent, when anInteger does not know how to subtract the receiver.
  2305      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."
  2306 
  2308 
  2307     anInteger > 0 ifTrue:[
  2309     anInteger > 0 ifTrue:[
  2308 	sign > 0 ifTrue:[
  2310         sign > 0 ifTrue:[
  2309 	    ^ self absFastMinus:anInteger sign:-1
  2311             ^ self absFastMinus:anInteger sign:-1
  2310 	].
  2312         ].
  2311 	^ self absFastPlus:anInteger sign:1
  2313         ^ self absFastPlus:anInteger sign:1
  2312     ].
  2314     ].
  2313     anInteger == 0 ifTrue:[
  2315     anInteger == 0 ifTrue:[
  2314 	^ self negated
  2316         ^ self negated
  2315     ].
  2317     ].
  2316     sign > 0 ifTrue:[
  2318     sign > 0 ifTrue:[
  2317 	^ self absFastPlus:anInteger negated sign:-1
  2319         ^ self absFastPlus:anInteger negated sign:-1
  2318     ].
  2320     ].
  2319 
  2321 
  2320     self > anInteger ifTrue:[
  2322     self > anInteger ifTrue:[
  2321 	^ self absFastMinus:anInteger asLargeInteger sign:-1
  2323         ^ self absFastMinus:anInteger asLargeInteger sign:-1
  2322     ] ifFalse:[
  2324     ] ifFalse:[
  2323 	^ anInteger asLargeInteger absFastMinus:self sign:-1
  2325         ^ anInteger asLargeInteger absFastMinus:self sign:-1
  2324     ].
  2326     ].
  2325 
  2327 
  2326     "
  2328     "
  2327      12345678901234567890
  2329      12345678901234567890
  2328      -12345678901234567890
  2330      -12345678901234567890
  2344     "/ results are always converted to smallInts, if possible.
  2346     "/ results are always converted to smallInts, if possible.
  2345     "/ therefore, a largeInt in the smallInt range is not allowed (possible)
  2347     "/ therefore, a largeInt in the smallInt range is not allowed (possible)
  2346     "/
  2348     "/
  2347     anInteger class == SmallInteger ifTrue:[^ false ].
  2349     anInteger class == SmallInteger ifTrue:[^ false ].
  2348     anInteger class == self class ifFalse:[
  2350     anInteger class == self class ifFalse:[
  2349 	^ super equalFromInteger:anInteger
  2351         ^ super equalFromInteger:anInteger
  2350     ].
  2352     ].
  2351     (anInteger sign == sign) ifFalse:[^ false].
  2353     (anInteger sign == sign) ifFalse:[^ false].
  2352     ^ self absEq:anInteger
  2354     ^ self absEq:anInteger
  2353 !
  2355 !
  2354 
  2356 
  2389     "trivial cases"
  2391     "trivial cases"
  2390     anInteger == 0 ifTrue:[^ 0].
  2392     anInteger == 0 ifTrue:[^ 0].
  2391     anInteger == 1 ifTrue:[^ self].
  2393     anInteger == 1 ifTrue:[^ self].
  2392 
  2394 
  2393     num := anInteger abs.
  2395     num := anInteger abs.
  2394     (num > 16r3FFFFF) ifTrue:[
  2396     SmallInteger maxBytes == 8 ifTrue:[
  2395 	"if num is too big (so that multiplying by a byte could create a Large)"
  2397         (num > 16r3FFFFFFF) ifTrue:[
  2396 
  2398             "if num is too big (so that multiplying by a byte could create a Large)"
  2397 	^ anInteger retry:#* coercing:self
  2399             ^ anInteger retry:#* coercing:self
       
  2400         ].
       
  2401     ] ifFalse:[    
       
  2402         (num > 16r3FFFFF) ifTrue:[
       
  2403             "if num is too big (so that multiplying by a byte could create a Large)"
       
  2404             ^ anInteger retry:#* coercing:self
       
  2405         ].
  2398     ].
  2406     ].
  2399 
  2407 
  2400     len := digitByteArray size.
  2408     len := digitByteArray size.
  2401 
  2409 
  2402     val := num.
  2410     val := num.
  2403     val <= 16rFF ifTrue:[
  2411     val <= 16rFF ifTrue:[
  2404 	lResult := len + 1.
  2412         lResult := len + 1.
  2405     ] ifFalse:[
  2413     ] ifFalse:[
  2406 	val <= 16rFFFF ifTrue:[
  2414         val <= 16rFFFF ifTrue:[
  2407 	    lResult := len + 2
  2415             lResult := len + 2
  2408 	] ifFalse:[
  2416         ] ifFalse:[
  2409 	    val <= 16rFFFFFF ifTrue:[
  2417             val <= 16rFFFFFF ifTrue:[
  2410 		lResult := len + 4.
  2418                 lResult := len + 4.
  2411 	    ] ifFalse:[
  2419             ] ifFalse:[
  2412 		lResult := len + 6.
  2420                 val <= 16rFFFFFFFF ifTrue:[
  2413 	    ]
  2421                     lResult := len + 6.
  2414 	]
  2422                 ] ifFalse:[
       
  2423                     val <= 16rFFFFFFFFFF ifTrue:[
       
  2424                         lResult := len + 8.
       
  2425                     ] ifFalse:[
       
  2426                         val <= 16rFFFFFFFFFF ifTrue:[
       
  2427                             lResult := len + 10.
       
  2428                         ] ifFalse:[
       
  2429                             val <= 16rFFFFFFFFFFFF ifTrue:[
       
  2430                                 lResult := len + 12.
       
  2431                             ] ifFalse:[
       
  2432                                 lResult := len + 14.
       
  2433                             ]
       
  2434                         ]
       
  2435                     ]
       
  2436                 ]
       
  2437             ]
       
  2438         ]
  2415     ].
  2439     ].
  2416     resultDigitByteArray := ByteArray uninitializedNew:lResult.
  2440     resultDigitByteArray := ByteArray uninitializedNew:lResult.
  2417     result := self class basicNew setDigits:resultDigitByteArray.
  2441     result := self class basicNew setDigits:resultDigitByteArray.
  2418 
  2442 
  2419     anInteger < 0 ifTrue:[
  2443     anInteger < 0 ifTrue:[
  2420 	sign > 0 ifTrue:[
  2444         sign > 0 ifTrue:[
  2421 	    result setSign:-1
  2445             result setSign:-1
  2422 	].
  2446         ].
  2423     ] ifFalse:[
  2447     ] ifFalse:[
  2424 	sign < 0 ifTrue:[
  2448         sign < 0 ifTrue:[
  2425 	    result setSign:sign
  2449             result setSign:sign
  2426 	]
  2450         ]
  2427     ].
  2451     ].
  2428 
  2452 
  2429     ok := false.
  2453     ok := false.
  2430 %{
  2454 %{
  2431     OBJ __digitByteArray = __INST(digitByteArray);
  2455     OBJ __digitByteArray = __INST(digitByteArray);
  2432 
  2456 
  2433     if (__isSmallInteger(len)
  2457     if (__isSmallInteger(len)
  2434      && __isByteArray(__digitByteArray)
  2458      && __isByteArray(__digitByteArray)
  2435      && __isByteArray(resultDigitByteArray)) {
  2459      && __isByteArray(resultDigitByteArray)) {
  2436 	INT _l = __intVal(len);
  2460         INT _l = __intVal(len);
  2437 	INT _v = __intVal(val);
  2461         INT _v = __intVal(val);
  2438 	unsigned INT _carry = 0;
  2462         unsigned INT _carry = 0;
  2439 	unsigned INT _prod;
  2463         unsigned INT _prod;
  2440 	unsigned char *digitP = __ByteArrayInstPtr(__digitByteArray)->ba_element;
  2464         unsigned char *digitP = __ByteArrayInstPtr(__digitByteArray)->ba_element;
  2441 	unsigned char *resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  2465         unsigned char *resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  2442 
  2466 
  2443 	/*
  2467         /*
  2444 	 * skipping zeros does not help much (a few percent) on
  2468          * skipping zeros does not help much (a few percent) on
  2445 	 * a P5 or other CPUS with a fast multiplier.
  2469          * a P5 or other CPUS with a fast multiplier.
  2446 	 * It may make more of a difference on CPUs with slower 0-multiply.
  2470          * It may make more of a difference on CPUs with slower 0-multiply.
  2447 	 */
  2471          * Late news: it actually hurts modern x86_64 cpus.
  2448 	while ((_l >= sizeof(INT)) && (((unsigned INT *)digitP)[0] == 0)) {
  2472          * So only reenable for specific CPUs after concrete benchmarks.
  2449 	    ((unsigned INT *)resultP)[0] = 0;
  2473          */
  2450 	    digitP += sizeof(INT);
  2474 #if 0
  2451 	    resultP += sizeof(INT);
  2475         while ((_l >= sizeof(INT)) && (((unsigned INT *)digitP)[0] == 0)) {
  2452 	    _l -= sizeof(INT);
  2476             ((unsigned INT *)resultP)[0] = 0;
  2453 	}
  2477             digitP += sizeof(INT);
       
  2478             resultP += sizeof(INT);
       
  2479             _l -= sizeof(INT);
       
  2480         }
       
  2481 #endif
  2454 
  2482 
  2455 #if defined(__LSBFIRST__)
  2483 #if defined(__LSBFIRST__)
  2456 # if defined (__GNUC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  2484 # if defined (__GNUC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  2457 	/*
  2485         /*
  2458 	 * can do it long-word-wise;
  2486          * can do it long-word-wise;
  2459 	 * 32*32 -> 64 multiplication
  2487          * 32*32 -> 64 multiplication
  2460 	 */
  2488          */
  2461 	while (_l > 3) {
  2489         while (_l > 3) {
  2462 	    unsigned __pHi, __pLow;
  2490             unsigned __pHi, __pLow;
  2463 	    unsigned __digit;
  2491             unsigned __digit;
  2464 
  2492 
  2465 	    /*
  2493             /*
  2466 	     * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
  2494              * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
  2467 	     * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
  2495              * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
  2468 	     */
  2496              */
  2469 	    __digit = ((unsigned long *)digitP)[0];
  2497             __digit = ((unsigned long *)digitP)[0];
  2470 	    asm ("mull %3               \n\
  2498             asm ("mull %3               \n\
  2471 		  addl %4,%%eax         \n\
  2499                   addl %4,%%eax         \n\
  2472 		  adcl $0,%%edx"
  2500                   adcl $0,%%edx"
  2473 		    : "=a"  (__pLow),
  2501                     : "=a"  (__pLow),
  2474 		      "=d"  (__pHi)
  2502                       "=d"  (__pHi)
  2475 		    : "0"   (__digit),
  2503                     : "0"   (__digit),
  2476 		      "1"   ((unsigned long)(_v)),
  2504                       "1"   ((unsigned long)(_v)),
  2477 		      "rm"  ((unsigned long)(_carry)) );
  2505                       "rm"  ((unsigned long)(_carry)) );
  2478 
  2506 
  2479 	    ((unsigned long *)resultP)[0] = __pLow;
  2507             ((unsigned long *)resultP)[0] = __pLow;
  2480 	    _carry = __pHi;
  2508             _carry = __pHi;
  2481 	    digitP += 4;
  2509             digitP += 4;
  2482 	    resultP += 4;
  2510             resultP += 4;
  2483 	    _l -= 4;
  2511             _l -= 4;
  2484 	}
  2512         }
  2485 # else /* not GNU-i386 */
  2513 # else /* not GNU-i386 */
  2486 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  2514 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  2487 	/*
  2515         /*
  2488 	 * can do it long-word-wise;
  2516          * can do it long-word-wise;
  2489 	 * 32*32 -> 64 multiplication
  2517          * 32*32 -> 64 multiplication
  2490 	 */
  2518          */
  2491 	while (_l > 3) {
  2519         while (_l > 3) {
  2492 	    unsigned __pLow;
  2520             unsigned __pLow;
  2493 	    unsigned digit;
  2521             unsigned digit;
  2494 
  2522 
  2495 	    /*
  2523             /*
  2496 	     * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
  2524              * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
  2497 	     * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
  2525              * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
  2498 	     */
  2526              */
  2499 /*
  2527 /*
  2500 	    digit = ((unsigned long *)digitP)[0];
  2528             digit = ((unsigned long *)digitP)[0];
  2501 	    edx::eax = (digit * _v);
  2529             edx::eax = (digit * _v);
  2502 	    edx::eax += _carry;
  2530             edx::eax += _carry;
  2503 	    ((unsigned long *)resultP)[0] = eax; -- pLow
  2531             ((unsigned long *)resultP)[0] = eax; -- pLow
  2504 	    _carry = edx; -- pHigh
  2532             _carry = edx; -- pHigh
  2505 	    digitP += 4;
  2533             digitP += 4;
  2506 	    resultP += 4;
  2534             resultP += 4;
  2507 */
  2535 */
  2508 	    digit = ((unsigned long *)digitP)[0];
  2536             digit = ((unsigned long *)digitP)[0];
  2509 	    asm {
  2537             asm {
  2510 		mov   eax, digit
  2538                 mov   eax, digit
  2511 		mov   edx, _v
  2539                 mov   edx, _v
  2512 		mul   edx
  2540                 mul   edx
  2513 		add   eax, _carry
  2541                 add   eax, _carry
  2514 		adc   edx, 0
  2542                 adc   edx, 0
  2515 		mov   __pLow, eax
  2543                 mov   __pLow, eax
  2516 		mov   _carry, edx
  2544                 mov   _carry, edx
  2517 	    }
  2545             }
  2518 
  2546 
  2519 	    ((unsigned long *)resultP)[0] = __pLow;
  2547             ((unsigned long *)resultP)[0] = __pLow;
  2520 	    digitP += 4;
  2548             digitP += 4;
  2521 	    resultP += 4;
  2549             resultP += 4;
  2522 	    _l -= 4;
  2550             _l -= 4;
  2523 	}
  2551         }
  2524 #  else /* not WIN32-i386 */
  2552 #  else /* not WIN32-i386 */
  2525 #   if defined(INT64)
  2553 #   if defined(INT64)
  2526 	if (_v <= 0xFFFFFFFFL) {
  2554         if (_v <= 0xFFFFFFFFL) {
  2527 	    /*
  2555             /* have 64bit ints; can do it int-wise
  2528 	     * have a 64bit int type ... good
  2556              *
  2529 	     */
  2557              * max: 0xFFFFFFFF * 0xFFFFFFFF -> 0xFFFFFFFE.0001
  2530 	    UINT64 _prod64;
  2558              * + maxCarry (0xFFFFFFFF)  -> 0xFFFFFFFF.0000
  2531 
  2559              */
  2532 	    /* have 64bit ints; can do it int-wise
  2560             while (_l >= (4+4+4+4)) {
  2533 	     *
  2561                 unsigned __t1, __t2, __t3, __t4;
  2534 	     * max: 0xFFFFFFFF * 0xFFFFFFFF -> 0xFFFFFFFE.0001
  2562                 UINT64 _prod64a, _prod64b, _prod64c, _prod64d;
  2535 	     * + maxCarry (0xFFFFFFFF)  -> 0xFFFFFFFF.0000
  2563 
  2536 	     */
  2564                 __t1 = ((unsigned *)digitP)[0];
  2537 	    while (_l > 3) {
  2565                 _prod64a = (INT64)_v;
  2538 		unsigned __t;
  2566                 _prod64a *= __t1;
  2539 
  2567                 _prod64a += _carry;
  2540 		__t = ((unsigned *)digitP)[0];
  2568                 ((unsigned *)resultP)[0] = _prod64a /* & 0xFFFFFFFFL */;
  2541 		digitP += 4;
  2569                 _carry = _prod64a >> 32;
  2542 		_prod64 = (INT64)_v;
  2570 
  2543 		_prod64 *= __t;
  2571                 __t2 = ((unsigned *)digitP)[1];
  2544 		_prod64 += _carry;
  2572                 _prod64b = (INT64)_v;
  2545 		((unsigned *)resultP)[0] = _prod64 /* & 0xFFFFFFFFL */;
  2573                 _prod64b *= __t2;
  2546 		_carry = _prod64 >> 32;
  2574                 _prod64b += _carry;
  2547 		resultP += 4;
  2575                 ((unsigned *)resultP)[1] = _prod64b /* & 0xFFFFFFFFL */;
  2548 		_l -= 4;
  2576                 _carry = _prod64b >> 32;
  2549 	    }
  2577                 
  2550 	    if (_l > 1) {
  2578                 __t3 = ((unsigned *)digitP)[2];
  2551 		unsigned short __t;
  2579                 _prod64c = (INT64)_v;
  2552 
  2580                 _prod64c *= __t3;
  2553 		__t = ((unsigned short *)digitP)[0];
  2581                 _prod64c += _carry;
  2554 		digitP += 2;
  2582                 ((unsigned *)resultP)[2] = _prod64c /* & 0xFFFFFFFFL */;
  2555 		_prod64 = (INT64)_v;
  2583                 _carry = _prod64c >> 32;
  2556 		_prod64 *= __t;
  2584 
  2557 		_prod64 += _carry;
  2585                 __t4 = ((unsigned *)digitP)[3];
  2558 		((unsigned short *)resultP)[0] = _prod64 /* & 0xFFFF */;
  2586                 _prod64d = (INT64)_v;
  2559 		_carry = _prod64 >> 16;
  2587                 _prod64d *= __t4;
  2560 		resultP += 2;
  2588                 _prod64d += _carry;
  2561 		_l -= 2;
  2589                 ((unsigned *)resultP)[3] = _prod64d /* & 0xFFFFFFFFL */;
  2562 	    }
  2590                 _carry = _prod64d >> 32;
  2563 	    if (_l > 0) {
  2591 
  2564 		_prod64 = *digitP++ * _v + _carry;
  2592                 digitP += (4+4+4+4);
  2565 		*resultP++ = _prod64 /* & 0xFF */;
  2593                 resultP += (4+4+4+4);
  2566 		_carry = _prod64 >> 8;
  2594                 _l -= (4+4+4+4);
  2567 		_l--;
  2595             }
  2568 	    }
  2596             while (_l >= 4) {
  2569 	}
  2597                 unsigned __t;
       
  2598                 UINT64 _prod64;
       
  2599 
       
  2600                 __t = ((unsigned *)digitP)[0];
       
  2601                 digitP += 4;
       
  2602                 _prod64 = (INT64)_v;
       
  2603                 _prod64 *= __t;
       
  2604                 _prod64 += _carry;
       
  2605                 ((unsigned *)resultP)[0] = _prod64 /* & 0xFFFFFFFFL */;
       
  2606                 _carry = _prod64 >> 32;
       
  2607                 resultP += 4;
       
  2608                 _l -= 4;
       
  2609             }
       
  2610             if (_l >= 2) {
       
  2611                 unsigned short __t;
       
  2612                 UINT64 _prod64;
       
  2613 
       
  2614                 __t = ((unsigned short *)digitP)[0];
       
  2615                 digitP += 2;
       
  2616                 _prod64 = (INT64)_v;
       
  2617                 _prod64 *= __t;
       
  2618                 _prod64 += _carry;
       
  2619                 ((unsigned short *)resultP)[0] = _prod64 /* & 0xFFFF */;
       
  2620                 _carry = _prod64 >> 16;
       
  2621                 resultP += 2;
       
  2622                 _l -= 2;
       
  2623             }
       
  2624             if (_l > 0) {
       
  2625                 UINT64 _prod64;
       
  2626                 _prod64 = *digitP++ * _v + _carry;
       
  2627                 *resultP++ = _prod64 /* & 0xFF */;
       
  2628                 _carry = _prod64 >> 8;
       
  2629                 _l--;
       
  2630             }
       
  2631         }
  2570 #   else /* no INT64 type */
  2632 #   else /* no INT64 type */
  2571 	if (_v <= 0xFFFF) {
  2633         if (_v <= 0xFFFF) {
  2572 	    /* can do it short-wise
  2634             /* can do it short-wise
  2573 	     *
  2635              *
  2574 	     * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
  2636              * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
  2575 	     * + maxCarry (0xFFFF)  -> 0xFFFF.0000
  2637              * + maxCarry (0xFFFF)  -> 0xFFFF.0000
  2576 	     */
  2638              */
  2577 	    while (_l > 1) {
  2639             while (_l > 1) {
  2578 		_prod = ((unsigned short *)digitP)[0] * _v + _carry;
  2640                 _prod = ((unsigned short *)digitP)[0] * _v + _carry;
  2579 		((unsigned short *)resultP)[0] = _prod /* & 0xFFFF */;
  2641                 ((unsigned short *)resultP)[0] = _prod /* & 0xFFFF */;
  2580 		_carry = _prod >> 16;
  2642                 _carry = _prod >> 16;
  2581 		digitP += 2;
  2643                 digitP += 2;
  2582 		resultP += 2;
  2644                 resultP += 2;
  2583 		_l -= 2;
  2645                 _l -= 2;
  2584 	    }
  2646             }
  2585 	}
  2647         }
  2586 #   endif /* no INT64 */
  2648 #   endif /* no INT64 */
  2587 #  endif /* not WIN32-i386 */
  2649 #  endif /* not WIN32-i386 */
  2588 # endif /* not GNU-i386 */
  2650 # endif /* not GNU-i386 */
  2589 #else /* not LSB_FIRST */
  2651 #else /* not LSB_FIRST */
  2590 
  2652 
  2591 # ifdef __mips__
  2653 # ifdef __mips__
  2592 #  define LOAD_WORD_WISE
  2654 #  define LOAD_WORD_WISE
  2593    /* no, STORE_WORD_WISE makes it slower */
  2655    /* no, STORE_WORD_WISE makes it slower */
  2594 # endif
  2656 # endif
  2595 
  2657 
  2596 	if (_v <= 0xFFFF) {
  2658         if (_v <= 0xFFFF) {
  2597 	    /* can do it short-wise
  2659             /* can do it short-wise
  2598 	     *
  2660              *
  2599 	     * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
  2661              * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
  2600 	     * + maxCarry (0xFFFF)  -> 0xFFFF.0000
  2662              * + maxCarry (0xFFFF)  -> 0xFFFF.0000
  2601 	     */
  2663              */
  2602 	    while (_l > 1) {
  2664             while (_l > 1) {
  2603 		unsigned int t;
  2665                 unsigned int t;
  2604 
  2666 
  2605 #if defined(LOAD_WORD_WISE)
  2667 #if defined(LOAD_WORD_WISE)
  2606 		/* better fetch short-wise */
  2668                 /* better fetch short-wise */
  2607 		t = ((unsigned short *)digitP)[0];
  2669                 t = ((unsigned short *)digitP)[0];
  2608 		digitP += 2;
  2670                 digitP += 2;
  2609 		t = ((t >> 8) | (t << 8)) & 0xFFFF;
  2671                 t = ((t >> 8) | (t << 8)) & 0xFFFF;
  2610 #else
  2672 #else
  2611 		t = (digitP[1]<<8) + digitP[0];
  2673                 t = (digitP[1]<<8) + digitP[0];
  2612 		digitP += 2;
  2674                 digitP += 2;
  2613 #endif
  2675 #endif
  2614 		_prod = t * _v + _carry;
  2676                 _prod = t * _v + _carry;
  2615 		_carry = _prod >> 16;
  2677                 _carry = _prod >> 16;
  2616 #if defined(STORE_WORD_WISE)
  2678 #if defined(STORE_WORD_WISE)
  2617 		/* better store short-wise */
  2679                 /* better store short-wise */
  2618 		_prod = ((_prod >> 8) | (_prod << 8)) & 0xFFFF;
  2680                 _prod = ((_prod >> 8) | (_prod << 8)) & 0xFFFF;
  2619 		((unsigned short *)resultP)[0] = _prod;
  2681                 ((unsigned short *)resultP)[0] = _prod;
  2620 #else
  2682 #else
  2621 		resultP[0] = _prod /* & 0xFF */;
  2683                 resultP[0] = _prod /* & 0xFF */;
  2622 		resultP[1] = (_prod>>8) /* & 0xFF */;
  2684                 resultP[1] = (_prod>>8) /* & 0xFF */;
  2623 #endif
  2685 #endif
  2624 		resultP += 2;
  2686                 resultP += 2;
  2625 		_l -= 2;
  2687                 _l -= 2;
  2626 	    }
  2688             }
  2627 	}
  2689         }
  2628 
  2690 
  2629 #endif /* LSB_FIRST */
  2691 #endif /* LSB_FIRST */
  2630 
  2692 
  2631 	/*
  2693         /*
  2632 	 * rest is done byte-wise
  2694          * rest is done byte-wise
  2633 	 */
  2695          */
  2634 	while (_l > 0) {
  2696         while (_l > 0) {
  2635 	    _prod = *digitP++ * _v + _carry;
  2697             _prod = *digitP++ * _v + _carry;
  2636 	    *resultP++ = _prod /* & 0xFF */;
  2698             *resultP++ = _prod /* & 0xFF */;
  2637 	    _carry = _prod >> 8;
  2699             _carry = _prod >> 8;
  2638 	    _l--;
  2700             _l--;
  2639 	}
  2701         }
  2640 
  2702 
  2641 	_l = __intVal(lResult) - __intVal(len);
  2703         _l = __intVal(lResult) - __intVal(len);
  2642 
  2704 
  2643 	/*
  2705         /*
  2644 	 * remaining carry
  2706          * remaining carry
  2645 	 */
  2707          */
  2646 	while (_carry) {
  2708         while (_carry) {
  2647 	    *resultP++ = _carry /* & 0xFF */;
  2709             *resultP++ = _carry /* & 0xFF */;
  2648 	    _carry >>= 8;
  2710             _carry >>= 8;
  2649 	    _l--;
  2711             _l--;
  2650 	}
  2712         }
  2651 
  2713 
  2652 	/*
  2714         /*
  2653 	 * remaining zeros
  2715          * remaining zeros
  2654 	 */
  2716          */
  2655 	while (_l--) {
  2717         while (_l--) {
  2656 	    *resultP++ = 0;
  2718             *resultP++ = 0;
  2657 	}
  2719         }
  2658 
  2720 
  2659 	/*
  2721         /*
  2660 	 * need compress ?
  2722          * need compress ?
  2661 	 */
  2723          */
  2662 	if (resultP[-1]) {
  2724         if (resultP[-1]) {
  2663 	    /*
  2725             /*
  2664 	     * no
  2726              * no
  2665 	     */
  2727              */
  2666 	    RETURN(result);
  2728             RETURN(result);
  2667 	}
  2729         }
  2668 
  2730 
  2669 	ok = true;
  2731         ok = true;
  2670     }
  2732     }
  2671 %}.
  2733 %}.
  2672     "
  2734     "
  2673      fall back - normally not reached
  2735      fall back - normally not reached
  2674      (could make it a primitive-failure as well)
  2736      (could make it a primitive-failure as well)
  2675     "
  2737     "
  2676     ok ifFalse:[
  2738     ok ifFalse:[
  2677 	carry := 0.
  2739         carry := 0.
  2678 	1 to:len do:[:i |
  2740         1 to:len do:[:i |
  2679 	    prod := (digitByteArray basicAt:i) * val + carry.
  2741             prod := (digitByteArray basicAt:i) * val + carry.
  2680 	    resultDigitByteArray basicAt:i put:(prod bitAnd:16rFF).
  2742             resultDigitByteArray basicAt:i put:(prod bitAnd:16rFF).
  2681 	    carry := prod bitShift:-8.
  2743             carry := prod bitShift:-8.
  2682 	].
  2744         ].
  2683 	[carry ~~ 0] whileTrue:[
  2745         [carry ~~ 0] whileTrue:[
  2684 	    len := len + 1.
  2746             len := len + 1.
  2685 	    resultDigitByteArray basicAt:len put:(carry bitAnd:16rFF).
  2747             resultDigitByteArray basicAt:len put:(carry bitAnd:16rFF).
  2686 	    carry := carry bitShift:-8
  2748             carry := carry bitShift:-8
  2687 	].
  2749         ].
  2688 	[len < lResult] whileTrue:[
  2750         [len < lResult] whileTrue:[
  2689 	    len := len + 1.
  2751             len := len + 1.
  2690 	    resultDigitByteArray basicAt:len put:0
  2752             resultDigitByteArray basicAt:len put:0
  2691 	]
  2753         ]
  2692     ].
  2754     ].
  2693     ^ result compressed
  2755     ^ result compressed
  2694 !
  2756 !
  2695 
  2757 
  2696 sumFromInteger:anInteger
  2758 sumFromInteger:anInteger
  2697     "sent, when anInteger does not know how to add the receiver.
  2759     "sent, when anInteger does not know how to add the receiver.
  2698      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)"
  2699 
  2761 
  2700     anInteger > 0 ifTrue:[
  2762     anInteger > 0 ifTrue:[
  2701 	sign > 0 ifTrue:[
  2763         sign > 0 ifTrue:[
  2702 	    ^ self absFastPlus:anInteger sign:1
  2764             ^ self absFastPlus:anInteger sign:1
  2703 	].
  2765         ].
  2704 	^ self absFastMinus:anInteger sign:-1
  2766         ^ self absFastMinus:anInteger sign:-1
  2705     ].
  2767     ].
  2706     anInteger == 0 ifTrue:[
  2768     anInteger == 0 ifTrue:[
  2707 	^ self
  2769         ^ self
  2708     ].
  2770     ].
  2709     sign > 0 ifTrue:[
  2771     sign > 0 ifTrue:[
  2710 	^ self absFastMinus:anInteger sign:1
  2772         ^ self absFastMinus:anInteger sign:1
  2711     ].
  2773     ].
  2712     ^ self absFastPlus:anInteger sign:-1
  2774     ^ self absFastPlus:anInteger sign:-1
  2713 
  2775 
  2714 
  2776 
  2715     "
  2777     "
  2803             (dividend absSubtract: divisor) ifFalse:[ "result == 0"
  2865             (dividend absSubtract: divisor) ifFalse:[ "result == 0"
  2804                 ^ Array with:quo compressed with:0
  2866                 ^ Array with:quo compressed with:0
  2805             ].
  2867             ].
  2806         ].
  2868         ].
  2807         shift := shift - 1.
  2869         shift := shift - 1.
  2808         divisor div2.
  2870         divisor := divisor div2.
  2809     ].
  2871     ].
  2810     ^ Array with:quo compressed with:dividend compressed
  2872     ^ Array with:quo compressed with:dividend compressed
  2811 
  2873 
  2812     "
  2874     "
  2813      Time millisecondsToRun:[ 10000 timesRepeat:[  16000000000 absDivMod:4000000000] ]
  2875      Time millisecondsToRun:[ 10000 timesRepeat:[  16000000000 absDivMod:4000000000] ]
  2831      d2   "{ Class: SmallInteger }"
  2893      d2   "{ Class: SmallInteger }"
  2832      otherDigitByteArray |
  2894      otherDigitByteArray |
  2833 
  2895 
  2834 %{  /* NOCONTEXT */
  2896 %{  /* NOCONTEXT */
  2835     if (__isLargeInteger(aLargeInteger)) {
  2897     if (__isLargeInteger(aLargeInteger)) {
  2836 	OBJ _digitByteArray = __INST(digitByteArray);
  2898         OBJ _digitByteArray = __INST(digitByteArray);
  2837 	OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  2899         OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  2838 
  2900 
  2839 	if (__isByteArray(_digitByteArray)
  2901         if (__isByteArray(_digitByteArray)
  2840 	 && __isByteArray(_otherDigitByteArray)) {
  2902          && __isByteArray(_otherDigitByteArray)) {
  2841 	    INT _myLen = __byteArraySize(_digitByteArray);
  2903             INT _myLen = __byteArraySize(_digitByteArray);
  2842 	    INT _otherLen = __byteArraySize(_otherDigitByteArray);
  2904             INT _otherLen = __byteArraySize(_otherDigitByteArray);
  2843 
  2905 
  2844 	    unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  2906             unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  2845 	    unsigned char *_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  2907             unsigned char *_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  2846 
  2908 
  2847 	    if (_myLen == _otherLen) {
  2909             if (_myLen == _otherLen) {
  2848 tryAgain:
  2910 tryAgain:
  2849 		while (_myLen >= (sizeof(INT)*4)) {
  2911                 while (_myLen >= (sizeof(INT)*4)) {
  2850 		    if ( ((unsigned INT *)_myDigits)[0] != ((unsigned INT *)_otherDigits)[0]) {
  2912                     if ( ((unsigned INT *)_myDigits)[0] != ((unsigned INT *)_otherDigits)[0]) {
  2851 			RETURN(false);
  2913                         RETURN(false);
  2852 		    }
  2914                     }
  2853 		    if ( ((unsigned INT *)_myDigits)[1] != ((unsigned INT *)_otherDigits)[1]) {
  2915                     if ( ((unsigned INT *)_myDigits)[1] != ((unsigned INT *)_otherDigits)[1]) {
  2854 			RETURN(false);
  2916                         RETURN(false);
  2855 		    }
  2917                     }
  2856 		    if ( ((unsigned INT *)_myDigits)[2] != ((unsigned INT *)_otherDigits)[2]) {
  2918                     if ( ((unsigned INT *)_myDigits)[2] != ((unsigned INT *)_otherDigits)[2]) {
  2857 			RETURN(false);
  2919                         RETURN(false);
  2858 		    }
  2920                     }
  2859 		    if ( ((unsigned INT *)_myDigits)[3] != ((unsigned INT *)_otherDigits)[3]) {
  2921                     if ( ((unsigned INT *)_myDigits)[3] != ((unsigned INT *)_otherDigits)[3]) {
  2860 			RETURN(false);
  2922                         RETURN(false);
  2861 		    }
  2923                     }
  2862 		    _myDigits += sizeof(INT)*4;
  2924                     _myDigits += sizeof(INT)*4;
  2863 		    _otherDigits += sizeof(INT)*4;
  2925                     _otherDigits += sizeof(INT)*4;
  2864 		    _myLen -= sizeof(INT)*4;
  2926                     _myLen -= sizeof(INT)*4;
  2865 		}
  2927                 }
  2866 		while (_myLen >= (sizeof(INT))) {
  2928                 while (_myLen >= (sizeof(INT))) {
  2867 		    if ( *(unsigned INT *)_myDigits != *(unsigned INT *)_otherDigits) {
  2929                     if ( *(unsigned INT *)_myDigits != *(unsigned INT *)_otherDigits) {
  2868 			RETURN(false);
  2930                         RETURN(false);
  2869 		    }
  2931                     }
  2870 		    _myDigits += sizeof(INT);
  2932                     _myDigits += sizeof(INT);
  2871 		    _otherDigits += sizeof(INT);
  2933                     _otherDigits += sizeof(INT);
  2872 		    _myLen -= sizeof(INT);
  2934                     _myLen -= sizeof(INT);
  2873 		}
  2935                 }
  2874 		while (_myLen > 0) {
  2936                 while (_myLen > 0) {
  2875 		    if ( *_myDigits != *_otherDigits) {
  2937                     if ( *_myDigits != *_otherDigits) {
  2876 			RETURN(false);
  2938                         RETURN(false);
  2877 		    }
  2939                     }
  2878 		    _myDigits++;
  2940                     _myDigits++;
  2879 		    _otherDigits++;
  2941                     _otherDigits++;
  2880 		    _myLen--;
  2942                     _myLen--;
  2881 		}
  2943                 }
  2882 		RETURN(true);
  2944                 RETURN(true);
  2883 	    }
  2945             }
  2884 	    /* care for unnormalized ints */
  2946             /* care for unnormalized ints */
  2885 	    while ((_myLen > 0) && (_myDigits[_myLen-1] == 0)) _myLen--;
  2947             while ((_myLen > 0) && (_myDigits[_myLen-1] == 0)) _myLen--;
  2886 	    while ((_otherLen > 0) && (_otherDigits[_otherLen-1] == 0)) _otherLen--;
  2948             while ((_otherLen > 0) && (_otherDigits[_otherLen-1] == 0)) _otherLen--;
  2887 	    if (_myLen == _otherLen) goto tryAgain;
  2949             if (_myLen == _otherLen) goto tryAgain;
  2888 	    RETURN(false);
  2950             RETURN(false);
  2889 	}
  2951         }
  2890     }
  2952     }
  2891 %}.
  2953 %}.
  2892 
  2954 
  2893     len1 := digitByteArray size.
  2955     len1 := digitByteArray size.
  2894     otherDigitByteArray := aLargeInteger digitBytes.
  2956     otherDigitByteArray := aLargeInteger digitBytes.
  2898     "/ when properly normalized;
  2960     "/ when properly normalized;
  2899     "/ but we are tolerant here, to allow for unnormalized
  2961     "/ but we are tolerant here, to allow for unnormalized
  2900     "/ numbers to be compared ...
  2962     "/ numbers to be compared ...
  2901 
  2963 
  2902     [(digitByteArray basicAt:len1) == 0] whileTrue:[
  2964     [(digitByteArray basicAt:len1) == 0] whileTrue:[
  2903 	len1 := len1 - 1
  2965         len1 := len1 - 1
  2904     ].
  2966     ].
  2905     [(otherDigitByteArray basicAt:len2) == 0] whileTrue:[
  2967     [(otherDigitByteArray basicAt:len2) == 0] whileTrue:[
  2906 	len2 := len2 - 1
  2968         len2 := len2 - 1
  2907     ].
  2969     ].
  2908     (len1 ~~ len2) ifTrue:[^ false].
  2970     (len1 ~~ len2) ifTrue:[^ false].
  2909     [len1 > 0] whileTrue:[
  2971     [len1 > 0] whileTrue:[
  2910 	d1 := digitByteArray basicAt:len1.
  2972         d1 := digitByteArray basicAt:len1.
  2911 	d2 := otherDigitByteArray basicAt:len1.
  2973         d2 := otherDigitByteArray basicAt:len1.
  2912 	(d1 ~~ d2) ifTrue:[^ false].
  2974         (d1 ~~ d2) ifTrue:[^ false].
  2913 	len1 := len1 - 1
  2975         len1 := len1 - 1
  2914     ].
  2976     ].
  2915     ^ true
  2977     ^ true
  2916 
  2978 
  2917     "Modified: / 8.5.1999 / 18:37:02 / cg"
  2979     "Modified: / 8.5.1999 / 18:37:02 / cg"
  2918 !
  2980 !
  2927      count    "{ Class: SmallInteger }"
  2989      count    "{ Class: SmallInteger }"
  2928      newDigitByteArray result
  2990      newDigitByteArray result
  2929      ok|
  2991      ok|
  2930 
  2992 
  2931     aPositiveSmallInteger == 0 ifTrue:[
  2993     aPositiveSmallInteger == 0 ifTrue:[
  2932 	^ ZeroDivide raiseRequestWith:thisContext
  2994         ^ ZeroDivide raiseRequestWith:thisContext
  2933     ].
  2995     ].
  2934 
  2996 
  2935 "This cannot happen (if always normalized)
  2997 "This cannot happen (if always normalized)
  2936     self < aPositiveSmallInteger ifTrue:[
  2998     self < aPositiveSmallInteger ifTrue:[
  2937 	^ Array with:0 with:self
  2999         ^ Array with:0 with:self
  2938     ].
  3000     ].
  2939 "
  3001 "
  2940     count := digitByteArray size.
  3002     count := digitByteArray size.
  2941     result := self class basicNew numberOfDigits:count.
  3003     result := self class basicNew numberOfDigits:count.
  2942     newDigitByteArray := result digitBytes.
  3004     newDigitByteArray := result digitBytes.
  2947     __digits = __INST(digitByteArray);
  3009     __digits = __INST(digitByteArray);
  2948 
  3010 
  2949     if (__isByteArray(__digits)
  3011     if (__isByteArray(__digits)
  2950      && __isByteArray(newDigitByteArray)
  3012      && __isByteArray(newDigitByteArray)
  2951      && __bothSmallInteger(count, aPositiveSmallInteger)) {
  3013      && __bothSmallInteger(count, aPositiveSmallInteger)) {
  2952 	unsigned INT rest = 0;
  3014         unsigned INT rest = 0;
  2953 	int index = __intVal(count);
  3015         int index = __intVal(count);
  2954 	int index0;
  3016         int index0;
  2955 	unsigned INT divisor = __intVal(aPositiveSmallInteger);
  3017         unsigned INT divisor = __intVal(aPositiveSmallInteger);
  2956 	unsigned char *digitBytes = __ByteArrayInstPtr(__digits)->ba_element;
  3018         unsigned char *digitBytes = __ByteArrayInstPtr(__digits)->ba_element;
  2957 	unsigned char *resultBytes = __ByteArrayInstPtr(newDigitByteArray)->ba_element;
  3019         unsigned char *resultBytes = __ByteArrayInstPtr(newDigitByteArray)->ba_element;
  2958 
  3020 
  2959 	index0 = index - 1;
  3021         index0 = index - 1;
  2960 
  3022 
  2961 # if (__POINTER_SIZE__ == 8)
  3023 # if (__POINTER_SIZE__ == 8)
  2962 	if (sizeof(int) == 4) {
  3024         if (sizeof(int) == 4) {
  2963 	    /*
  3025             /*
  2964 	     * divide int-wise
  3026              * divide int-wise
  2965 	     */
  3027              */
  2966 	    if (divisor <= 0xFFFFFFFF) {
  3028             if (divisor <= 0xFFFFFFFF) {
  2967 		if ((index & 3) == 0) { /* even number of int32's */
  3029                 if ((index & 3) == 0) { /* even number of int32's */
  2968 		    while (index > 3) {
  3030                     while (index > 3) {
  2969 			unsigned INT t;
  3031                         unsigned INT t;
  2970 			unsigned INT div;
  3032                         unsigned INT div;
  2971 
  3033 
  2972 			index -= 4;
  3034                         index -= 4;
  2973 # if defined(__LSBFIRST__)
  3035 # if defined(__LSBFIRST__)
  2974 			t = *((unsigned int *)(&digitBytes[index]));
  3036                         t = *((unsigned int *)(&digitBytes[index]));
  2975 # else
  3037 # else
  2976 			t = digitBytes[index+3];
  3038                         t = digitBytes[index+3];
  2977 			t = (t << 8) | digitBytes[index+2];
  3039                         t = (t << 8) | digitBytes[index+2];
  2978 			t = (t << 8) | digitBytes[index+1];
  3040                         t = (t << 8) | digitBytes[index+1];
  2979 			t = (t << 8) | digitBytes[index];
  3041                         t = (t << 8) | digitBytes[index];
  2980 # endif
  3042 # endif
  2981 			t = t | (rest << 32);
  3043                         t = t | (rest << 32);
  2982 			div = t / divisor;
  3044                         div = t / divisor;
  2983 			rest = t % divisor;
  3045                         rest = t % divisor;
  2984 # if defined(__LSBFIRST__)
  3046 # if defined(__LSBFIRST__)
  2985 			*((unsigned int *)(&resultBytes[index])) = (div & 0xFFFFFFFF);
  3047                         *((unsigned int *)(&resultBytes[index])) = (div & 0xFFFFFFFF);
  2986 # else
  3048 # else
  2987 			resultBytes[index+3] = div >> 24;
  3049                         resultBytes[index+3] = div >> 24;
  2988 			resultBytes[index+2] = div >> 16;
  3050                         resultBytes[index+2] = div >> 16;
  2989 			resultBytes[index+1] = div >> 8;
  3051                         resultBytes[index+1] = div >> 8;
  2990 			resultBytes[index] = div /* & 0xFF */;
  3052                         resultBytes[index] = div /* & 0xFF */;
  2991 # endif
  3053 # endif
  2992 		    }
  3054                     }
  2993 		}
  3055                 }
  2994 	    }
  3056             }
  2995 	}
  3057         }
  2996 #endif
  3058 #endif
  2997 	/*
  3059         /*
  2998 	 * divide short-wise
  3060          * divide short-wise
  2999 	 */
  3061          */
  3000 	if (divisor <= 0xFFFF) {
  3062         if (divisor <= 0xFFFF) {
  3001 	    if ((index & 1) == 0) { /* even number of bytes */
  3063             if ((index & 1) == 0) { /* even number of bytes */
  3002 		while (index > 1) {
  3064                 while (index > 1) {
  3003 		    unsigned INT t;
  3065                     unsigned INT t;
  3004 		    unsigned INT div;
  3066                     unsigned INT div;
  3005 
  3067 
  3006 		    index -= 2;
  3068                     index -= 2;
  3007 #if defined(__LSBFIRST__)
  3069 #if defined(__LSBFIRST__)
  3008 		    t = *((unsigned short *)(&digitBytes[index]));
  3070                     t = *((unsigned short *)(&digitBytes[index]));
  3009 #else
  3071 #else
  3010 		    t = digitBytes[index+1];
  3072                     t = digitBytes[index+1];
  3011 		    t = (t << 8) | digitBytes[index];
  3073                     t = (t << 8) | digitBytes[index];
  3012 #endif
  3074 #endif
  3013 		    t = t | (rest << 16);
  3075                     t = t | (rest << 16);
  3014 		    div = t / divisor;
  3076                     div = t / divisor;
  3015 		    rest = t % divisor;
  3077                     rest = t % divisor;
  3016 #if defined(__LSBFIRST__)
  3078 #if defined(__LSBFIRST__)
  3017 		    *((unsigned short *)(&resultBytes[index])) = (div & 0xFFFF);
  3079                     *((unsigned short *)(&resultBytes[index])) = (div & 0xFFFF);
  3018 #else
  3080 #else
  3019 		    resultBytes[index+1] = div >> 8;
  3081                     resultBytes[index+1] = div >> 8;
  3020 		    resultBytes[index] = div /* & 0xFF */;
  3082                     resultBytes[index] = div /* & 0xFF */;
  3021 #endif
  3083 #endif
  3022 		}
  3084                 }
  3023 	    }
  3085             }
  3024 	}
  3086         }
  3025 	while (index > 0) {
  3087         while (index > 0) {
  3026 	    unsigned INT t;
  3088             unsigned INT t;
  3027 
  3089 
  3028 	    index--;
  3090             index--;
  3029 	    t = digitBytes[index];
  3091             t = digitBytes[index];
  3030 	    t = t | (rest << 8);
  3092             t = t | (rest << 8);
  3031 	    resultBytes[index] = t / divisor;
  3093             resultBytes[index] = t / divisor;
  3032 	    rest = t % divisor;
  3094             rest = t % divisor;
  3033 	}
  3095         }
  3034 	prevRest = __mkSmallInteger(rest);
  3096         prevRest = __mkSmallInteger(rest);
  3035 
  3097 
  3036 	/*
  3098         /*
  3037 	 * no need to normalize ?
  3099          * no need to normalize ?
  3038 	 */
  3100          */
  3039 	index = index0;
  3101         index = index0;
  3040 	while ((index >= sizeof(INT)) && (resultBytes[index]==0)) {
  3102         while ((index >= sizeof(INT)) && (resultBytes[index]==0)) {
  3041 	    index--;
  3103             index--;
  3042 	}
  3104         }
  3043 
  3105 
  3044 	if (index == index0) {
  3106         if (index == index0) {
  3045 	    if (index > sizeof(INT)) {
  3107             if (index > sizeof(INT)) {
  3046 		RETURN ( __ARRAY_WITH2(result, prevRest));
  3108                 RETURN ( __ARRAY_WITH2(result, prevRest));
  3047 	    }
  3109             }
  3048 	    if ((index == sizeof(INT))
  3110             if ((index == sizeof(INT))
  3049 	    && resultBytes[index0] >= 0x40) {
  3111             && resultBytes[index0] >= 0x40) {
  3050 		RETURN ( __ARRAY_WITH2(result, prevRest));
  3112                 RETURN ( __ARRAY_WITH2(result, prevRest));
  3051 	    }
  3113             }
  3052 	}
  3114         }
  3053 
  3115 
  3054 	/*
  3116         /*
  3055 	 * must compress
  3117          * must compress
  3056 	 */
  3118          */
  3057 	ok = true;
  3119         ok = true;
  3058     }
  3120     }
  3059 %}.
  3121 %}.
  3060     "
  3122     "
  3061      slow code - not normally reached
  3123      slow code - not normally reached
  3062      (could also do a primitiveFailure here)
  3124      (could also do a primitiveFailure here)
  3063     "
  3125     "
  3064     ok ifFalse:[
  3126     ok ifFalse:[
  3065 	^ self absDivMod:(self class value:aPositiveSmallInteger).
  3127         ^ self absDivMod:(self class value:aPositiveSmallInteger).
  3066     ].
  3128     ].
  3067 
  3129 
  3068     ^ Array with:(result compressed) with:prevRest
  3130     ^ Array with:(result compressed) with:prevRest
  3069 
  3131 
  3070     "
  3132     "
  3092     "/ the following code only works with
  3154     "/ the following code only works with
  3093     "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255
  3155     "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255
  3094 
  3156 
  3095     ((aSmallInteger < (SmallInteger minVal + 255))
  3157     ((aSmallInteger < (SmallInteger minVal + 255))
  3096     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
  3158     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
  3097 	^ self absMinus:(self class value:aSmallInteger) sign:newSign.
  3159         ^ self absMinus:(self class value:aSmallInteger) sign:newSign.
  3098     ].
  3160     ].
  3099 
  3161 
  3100     len := digitByteArray size.
  3162     len := digitByteArray size.
  3101 
  3163 
  3102     rsltLen := len "+ 1".
  3164     rsltLen := len "+ 1".
  3106     borrow := aSmallInteger abs.
  3168     borrow := aSmallInteger abs.
  3107 
  3169 
  3108 %{
  3170 %{
  3109     if (__isByteArray(__INST(digitByteArray))
  3171     if (__isByteArray(__INST(digitByteArray))
  3110      && __isByteArray(resultDigitByteArray)) {
  3172      && __isByteArray(resultDigitByteArray)) {
  3111 	unsigned INT __borrow = __intVal(borrow);
  3173         unsigned INT __borrow = __intVal(borrow);
  3112 	INT __diff;
  3174         INT __diff;
  3113 	int __index = 1;
  3175         int __index = 1;
  3114 	int __len = __intVal(len);
  3176         int __len = __intVal(len);
  3115 	unsigned char *__digitP = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3177         unsigned char *__digitP = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3116 	unsigned char *__resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  3178         unsigned char *__resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  3117 	int __len3;
  3179         int __len3;
  3118 
  3180 
  3119 #if defined(__LSBFIRST__)
  3181 #if defined(__LSBFIRST__)
  3120 # if (__POINTER_SIZE__ == 8)
  3182 # if (__POINTER_SIZE__ == 8)
  3121 	/*
  3183         /*
  3122 	 * subtract int-wise
  3184          * subtract int-wise
  3123 	 */
  3185          */
  3124 	__len3 = __len - 3;
  3186         __len3 = __len - 3;
  3125 	while (__index < __len3) {
  3187         while (__index < __len3) {
  3126 	    /* do not make this into one expression - ask cg why */
  3188             /* do not make this into one expression - ask cg why */
  3127 	    __diff = ((unsigned int *)(__digitP + __index-1))[0];
  3189             __diff = ((unsigned int *)(__digitP + __index-1))[0];
  3128 	    __diff -= (__borrow & 0xFFFFFFFFL);
  3190             __diff -= (__borrow & 0xFFFFFFFFL);
  3129 	    __borrow >>= 32;
  3191             __borrow >>= 32;
  3130 	    if (__diff < 0) {
  3192             if (__diff < 0) {
  3131 		/* __diff += 0x100000000; */
  3193                 /* __diff += 0x100000000; */
  3132 		__borrow++;
  3194                 __borrow++;
  3133 	    }
  3195             }
  3134 	    ((unsigned int *)(__resultP+__index-1))[0] = __diff;
  3196             ((unsigned int *)(__resultP+__index-1))[0] = __diff;
  3135 	    __index += 4;
  3197             __index += 4;
  3136 	}
  3198         }
  3137 # endif
  3199 # endif
  3138 	/*
  3200         /*
  3139 	 * subtract short-wise
  3201          * subtract short-wise
  3140 	 */
  3202          */
  3141 	while (__index < __len) {
  3203         while (__index < __len) {
  3142 	    /* do not make this into one expression - ask cg why */
  3204             /* do not make this into one expression - ask cg why */
  3143 	    __diff = ((unsigned short *)(__digitP+__index-1))[0];
  3205             __diff = ((unsigned short *)(__digitP+__index-1))[0];
  3144 	    __diff -= (__borrow & 0xFFFF);
  3206             __diff -= (__borrow & 0xFFFF);
  3145 	    __borrow >>= 16;
  3207             __borrow >>= 16;
  3146 	    if (__diff < 0) {
  3208             if (__diff < 0) {
  3147 		/* __diff += 0x10000; */
  3209                 /* __diff += 0x10000; */
  3148 		__borrow++;
  3210                 __borrow++;
  3149 	    } else {
  3211             } else {
  3150 		if (__borrow == 0) {
  3212                 if (__borrow == 0) {
  3151 		    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
  3213                     ((unsigned short *)(__resultP+__index-1))[0] = __diff;
  3152 		    __index += 2;
  3214                     __index += 2;
  3153 
  3215 
  3154 		    /* nothing more to subtract .. */
  3216                     /* nothing more to subtract .. */
  3155 		    while (__index < __len) {
  3217                     while (__index < __len) {
  3156 			((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];
  3157 			__index += 2;
  3219                         __index += 2;
  3158 		    }
  3220                     }
  3159 		    if (__index <= __len) {
  3221                     if (__index <= __len) {
  3160 			__resultP[__index-1] = __digitP[__index-1];
  3222                         __resultP[__index-1] = __digitP[__index-1];
  3161 		    }
  3223                     }
  3162 		    break;
  3224                     break;
  3163 		}
  3225                 }
  3164 	    }
  3226             }
  3165 	    ((unsigned short *)(__resultP+__index-1))[0] = __diff;
  3227             ((unsigned short *)(__resultP+__index-1))[0] = __diff;
  3166 	    __index += 2;
  3228             __index += 2;
  3167 	}
  3229         }
  3168 #endif
  3230 #endif
  3169 	/*
  3231         /*
  3170 	 * subtract byte-wise
  3232          * subtract byte-wise
  3171 	 */
  3233          */
  3172 	while (__index <= __len) {
  3234         while (__index <= __len) {
  3173 	    __diff = __digitP[__index-1];
  3235             __diff = __digitP[__index-1];
  3174 	    __diff -= (__borrow & 0xFF);
  3236             __diff -= (__borrow & 0xFF);
  3175 	    __borrow >>= 8;
  3237             __borrow >>= 8;
  3176 	    if (__diff < 0) {
  3238             if (__diff < 0) {
  3177 		/* __diff += 0x100; */
  3239                 /* __diff += 0x100; */
  3178 		__borrow++;
  3240                 __borrow++;
  3179 	    } else {
  3241             } else {
  3180 		if (__borrow == 0) {
  3242                 if (__borrow == 0) {
  3181 		    __resultP[__index-1] = __diff;
  3243                     __resultP[__index-1] = __diff;
  3182 		    __index++;
  3244                     __index++;
  3183 
  3245 
  3184 		    /* nothing more to subtract .. */
  3246                     /* nothing more to subtract .. */
  3185 		    while (__index <= __len) {
  3247                     while (__index <= __len) {
  3186 			__resultP[__index-1] = __digitP[__index-1];
  3248                         __resultP[__index-1] = __digitP[__index-1];
  3187 			__index++;
  3249                         __index++;
  3188 		    }
  3250                     }
  3189 		    break;
  3251                     break;
  3190 		}
  3252                 }
  3191 	    }
  3253             }
  3192 	    __resultP[__index-1] = __diff;
  3254             __resultP[__index-1] = __diff;
  3193 	    __index++;
  3255             __index++;
  3194 	}
  3256         }
  3195 	lastDigit = __mkSmallInteger( __resultP[__index-1-1] );
  3257         lastDigit = __mkSmallInteger( __resultP[__index-1-1] );
  3196 	ok = true;
  3258         ok = true;
  3197     }
  3259     }
  3198 %}.
  3260 %}.
  3199 
  3261 
  3200     ok == true ifFalse:[        "/ cannot happen
  3262     ok == true ifFalse:[        "/ cannot happen
  3201 	index := 1.
  3263         index := 1.
  3202 	[borrow ~~ 0] whileTrue:[
  3264         [borrow ~~ 0] whileTrue:[
  3203 	    (index <= len) ifTrue:[
  3265             (index <= len) ifTrue:[
  3204 		diff := (digitByteArray basicAt:index) - (borrow bitAnd:16rFF).
  3266                 diff := (digitByteArray basicAt:index) - (borrow bitAnd:16rFF).
  3205 		borrow := borrow bitShift:-8.
  3267                 borrow := borrow bitShift:-8.
  3206 		diff < 0 ifTrue:[
  3268                 diff < 0 ifTrue:[
  3207 		    diff := diff + 256.
  3269                     diff := diff + 256.
  3208 		    borrow := borrow + 1.
  3270                     borrow := borrow + 1.
  3209 		]
  3271                 ]
  3210 	    ] ifFalse:[
  3272             ] ifFalse:[
  3211 		diff := borrow bitAnd:255.
  3273                 diff := borrow bitAnd:255.
  3212 		borrow := borrow bitShift:-8.
  3274                 borrow := borrow bitShift:-8.
  3213 	    ].
  3275             ].
  3214 	    resultDigitByteArray basicAt:index put:(lastDigit := diff).
  3276             resultDigitByteArray basicAt:index put:(lastDigit := diff).
  3215 	    index := index + 1
  3277             index := index + 1
  3216 	].
  3278         ].
  3217 	[index <= len] whileTrue:[
  3279         [index <= len] whileTrue:[
  3218 	    resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
  3280             resultDigitByteArray basicAt:index put:(lastDigit := digitByteArray basicAt:index).
  3219 	    index := index + 1
  3281             index := index + 1
  3220 	].
  3282         ].
  3221 	(index <= rsltLen) ifTrue:[
  3283         (index <= rsltLen) ifTrue:[
  3222 	    lastDigit := 0.
  3284             lastDigit := 0.
  3223 	]
  3285         ]
  3224     ].
  3286     ].
  3225 
  3287 
  3226     (lastDigit == 0 or:[rsltLen <= SmallInteger maxBytes]) ifTrue:[
  3288     (lastDigit == 0 or:[rsltLen <= SmallInteger maxBytes]) ifTrue:[
  3227 	^ result compressed.
  3289         ^ result compressed.
  3228     ].
  3290     ].
  3229     ^ result
  3291     ^ result
  3230 
  3292 
  3231     "
  3293     "
  3232      12345678900000000000 absFastMinus:1 sign:1
  3294      12345678900000000000 absFastMinus:1 sign:1
  3257     "/ the following code only works with
  3319     "/ the following code only works with
  3258     "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255
  3320     "/ smallIntegers in the range _MIN_INT+255 .. _MAX_INT-255
  3259 
  3321 
  3260     ((aSmallInteger < (SmallInteger minVal + 255))
  3322     ((aSmallInteger < (SmallInteger minVal + 255))
  3261     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
  3323     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
  3262 	^ self absPlus:(self class value:aSmallInteger) sign:newSign.
  3324         ^ self absPlus:(self class value:aSmallInteger) sign:newSign.
  3263     ].
  3325     ].
  3264 
  3326 
  3265     len := rsltLen := digitByteArray size.
  3327     len := rsltLen := digitByteArray size.
  3266     "/
  3328     "/
  3267     "/ there can only be an overflow from the high byte,
  3329     "/ there can only be an overflow from the high byte,
  3268     "/ if it is 255 (since the other number is definitely smaller)
  3330     "/ if it is 255 (since the other number is definitely smaller)
  3269     "/
  3331     "/
  3270     (digitByteArray at:len) == 16rFF ifTrue:[
  3332     (digitByteArray at:len) == 16rFF ifTrue:[
  3271 	rsltLen := len + 1.
  3333         rsltLen := len + 1.
  3272     ] ifFalse:[
  3334     ] ifFalse:[
  3273 	"/ or the argument has something in the high byte ..
  3335         "/ or the argument has something in the high byte ..
  3274 %{
  3336 %{
  3275 #if __POINTER_SIZE__ == 8
  3337 #if __POINTER_SIZE__ == 8
  3276 	if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
  3338         if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
  3277 	    rsltLen = __mkSmallInteger(__intVal(len) + 1);
  3339             rsltLen = __mkSmallInteger(__intVal(len) + 1);
  3278 	}
  3340         }
  3279 #else
  3341 #else
  3280 	if (__intVal(aSmallInteger) & 0xFF000000) {
  3342         if (__intVal(aSmallInteger) & 0xFF000000) {
  3281 	    rsltLen = __mkSmallInteger(__intVal(len) + 1);
  3343             rsltLen = __mkSmallInteger(__intVal(len) + 1);
  3282 	}
  3344         }
  3283 #endif
  3345 #endif
  3284 %}
  3346 %}
  3285     ].
  3347     ].
  3286 
  3348 
  3287     result := self class basicNew numberOfDigits:rsltLen sign:newSign.
  3349     result := self class basicNew numberOfDigits:rsltLen sign:newSign.
  3289 
  3351 
  3290 %{
  3352 %{
  3291     if (__isByteArray(__INST(digitByteArray))
  3353     if (__isByteArray(__INST(digitByteArray))
  3292      && __isByteArray(resultDigitByteArray)
  3354      && __isByteArray(resultDigitByteArray)
  3293      && __isSmallInteger(aSmallInteger)) {
  3355      && __isSmallInteger(aSmallInteger)) {
  3294 	/* carry is NOT unsigned (see negation below) */
  3356         /* carry is NOT unsigned (see negation below) */
  3295 	INT __carry = __intVal(aSmallInteger);
  3357         INT __carry = __intVal(aSmallInteger);
  3296 	int __index = 1;
  3358         int __index = 1;
  3297 	int __len = __intVal(len);
  3359         int __len = __intVal(len);
  3298 	unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
  3360         unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
  3299 	unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
  3361         unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
  3300 	INT __ptrDelta = __dst - __src;
  3362         INT __ptrDelta = __dst - __src;
  3301 	unsigned char *__srcLast = __src + __len - 1;
  3363         unsigned char *__srcLast = __src + __len - 1;
  3302 	int __rsltLen = __intVal(rsltLen);
  3364         int __rsltLen = __intVal(rsltLen);
  3303 
  3365 
  3304 	if (__carry < 0) {
  3366         if (__carry < 0) {
  3305 	    __carry = -__carry;
  3367             __carry = -__carry;
  3306 	}
  3368         }
  3307 
  3369 
  3308 #if defined(__LSBFIRST__)
  3370 #if defined(__LSBFIRST__)
  3309 # if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
  3371 # if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
  3310 #  if 0 /* NOTICE - the code below is 20% slower ... - why */
  3372 #  if 0 /* NOTICE - the code below is 20% slower ... - why */
  3311 	/*
  3373         /*
  3312 	 * add long-wise
  3374          * add long-wise
  3313 	 */
  3375          */
  3314 	asm("  jecxz nothingToDo                                      \n\
  3376         asm("  jecxz nothingToDo                                      \n\
  3315 	       movl  %%eax, %%esi      /* __src input */              \n\
  3377                movl  %%eax, %%esi      /* __src input */              \n\
  3316 	       movl  %%ebx, %%edi      /* __dst input */              \n\
  3378                movl  %%ebx, %%edi      /* __dst input */              \n\
  3317 								      \n\
  3379                                                                       \n\
  3318 	       /* the first 4-byte int */                             \n\
  3380                /* the first 4-byte int */                             \n\
  3319 	       lodsl                   /* fetch */                    \n\
  3381                lodsl                   /* fetch */                    \n\
  3320 	       addl  %%edx, %%eax      /* add */                      \n\
  3382                addl  %%edx, %%eax      /* add */                      \n\
  3321 	       stosl                   /* store */                    \n\
  3383                stosl                   /* store */                    \n\
  3322 	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
  3384                leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
  3323 	       jecxz doneLoop          /* any more ? */               \n\
  3385                jecxz doneLoop          /* any more ? */               \n\
  3324 	       /* remaining 4-byte ints */                            \n\
  3386                /* remaining 4-byte ints */                            \n\
  3325 	       jmp   addLoop                                          \n\
  3387                jmp   addLoop                                          \n\
  3326 								      \n\
  3388                                                                       \n\
  3327 	       .align 8                                               \n\
  3389                .align 8                                               \n\
  3328 	     addLoop:                                                 \n\
  3390              addLoop:                                                 \n\
  3329 	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
  3391                movl  0(%%esi), %%ebx   /* fetch  */                   \n\
  3330 	       jnc   copyLoop2                                        \n\
  3392                jnc   copyLoop2                                        \n\
  3331 	       movl  $0, %%eax                                        \n\
  3393                movl  $0, %%eax                                        \n\
  3332 	       leal  4(%%esi), %%esi                                  \n\
  3394                leal  4(%%esi), %%esi                                  \n\
  3333 	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
  3395                adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
  3334 	       leal  8(%%edi), %%edi                                  \n\
  3396                leal  8(%%edi), %%edi                                  \n\
  3335 	       movl  %%eax, -8(%%edi)  /* store */                    \n\
  3397                movl  %%eax, -8(%%edi)  /* store */                    \n\
  3336 	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
  3398                leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
  3337 	       jecxz doneLoop          /* any more ? */               \n\
  3399                jecxz doneLoop          /* any more ? */               \n\
  3338 								      \n\
  3400                                                                       \n\
  3339 	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
  3401                movl  0(%%esi), %%ebx   /* fetch  */                   \n\
  3340 	       movl  $0, %%eax                                        \n\
  3402                movl  $0, %%eax                                        \n\
  3341 	       leal  4(%%esi), %%esi                                  \
  3403                leal  4(%%esi), %%esi                                  \
  3342 	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
  3404                adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
  3343 	       movl  %%eax, -4(%%edi)  /* store */                    \n\
  3405                movl  %%eax, -4(%%edi)  /* store */                    \n\
  3344 								      \n\
  3406                                                                       \n\
  3345 	       loop  addLoop                                          \n\
  3407                loop  addLoop                                          \n\
  3346 	       jmp   doneLoop                                         \n\
  3408                jmp   doneLoop                                         \n\
  3347 								      \n\
  3409                                                                       \n\
  3348 	       .align 8                                               \n\
  3410                .align 8                                               \n\
  3349 	     copyLoop:                                                \n\
  3411              copyLoop:                                                \n\
  3350 	       movl  0(%%esi), %%ebx                                  \n\
  3412                movl  0(%%esi), %%ebx                                  \n\
  3351 	     copyLoop2:                                               \n\
  3413              copyLoop2:                                               \n\
  3352 	       add   $4, %%esi                                        \n\
  3414                add   $4, %%esi                                        \n\
  3353 	       add   $4, %%edi                                        \n\
  3415                add   $4, %%edi                                        \n\
  3354 	       movl  %%ebx, -4(%%edi)                                 \n\
  3416                movl  %%ebx, -4(%%edi)                                 \n\
  3355 	       loop  copyLoop                                         \n\
  3417                loop  copyLoop                                         \n\
  3356 								      \n\
  3418                                                                       \n\
  3357 	     doneLoop:                                                \n\
  3419              doneLoop:                                                \n\
  3358 	       movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
  3420                movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
  3359 	       adcl  $0, %%edx                                        \n\
  3421                adcl  $0, %%edx                                        \n\
  3360 	       movl  %%esi, %%eax      /* __src output */             \n\
  3422                movl  %%esi, %%eax      /* __src output */             \n\
  3361 	     nothingToDo:                                             \n\
  3423              nothingToDo:                                             \n\
  3362 	    " : "=d"  ((unsigned long)(__carry)),
  3424             " : "=d"  ((unsigned long)(__carry)),
  3363 		"=a"  (__src)
  3425                 "=a"  (__src)
  3364 	      : "1"   (__src),
  3426               : "1"   (__src),
  3365 		"b"   (__dst),
  3427                 "b"   (__dst),
  3366 		"c"   (__len / 4),
  3428                 "c"   (__len / 4),
  3367 		"0"   (__carry)
  3429                 "0"   (__carry)
  3368 	      : "esi", "edi");
  3430               : "esi", "edi");
  3369 
  3431 
  3370 #  else
  3432 #  else
  3371 	{
  3433         {
  3372 	    unsigned char *__srcLastX;
  3434             unsigned char *__srcLastX;
  3373 
  3435 
  3374 	    __srcLastX = __srcLast - 3 - 4;
  3436             __srcLastX = __srcLast - 3 - 4;
  3375 	    while (__src <= __srcLastX) {
  3437             while (__src <= __srcLastX) {
  3376 		unsigned int __sum, __sum2;
  3438                 unsigned int __sum, __sum2;
  3377 		unsigned __digit1, __digit2;
  3439                 unsigned __digit1, __digit2;
  3378 
  3440 
  3379 		__digit1 = ((unsigned *)__src)[0];
  3441                 __digit1 = ((unsigned *)__src)[0];
  3380 		__digit2 = ((unsigned *)__src)[1];
  3442                 __digit2 = ((unsigned *)__src)[1];
  3381 		asm ("addl %%edx,%%ecx          \n\
  3443                 asm ("addl %%edx,%%ecx          \n\
  3382 		      adcl $0, %%eax            \n\
  3444                       adcl $0, %%eax            \n\
  3383 		      movl $0, %%edx            \n\
  3445                       movl $0, %%edx            \n\
  3384 		      adcl $0, %%edx"
  3446                       adcl $0, %%edx"
  3385 			: "=d"  ((unsigned long)(__carry)),
  3447                         : "=d"  ((unsigned long)(__carry)),
  3386 			  "=c"  ((unsigned long)(__sum)),
  3448                           "=c"  ((unsigned long)(__sum)),
  3387 			  "=a"  ((unsigned long)(__sum2))
  3449                           "=a"  ((unsigned long)(__sum2))
  3388 			: "0"   ((unsigned long)(__carry)),
  3450                         : "0"   ((unsigned long)(__carry)),
  3389 			  "1"   (__digit1),
  3451                           "1"   (__digit1),
  3390 			  "2"   (__digit2));
  3452                           "2"   (__digit2));
  3391 
  3453 
  3392 		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3454                 ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3393 		((unsigned int *)(__src + __ptrDelta))[1] = __sum2;
  3455                 ((unsigned int *)(__src + __ptrDelta))[1] = __sum2;
  3394 
  3456 
  3395 		__src += 8;
  3457                 __src += 8;
  3396 
  3458 
  3397 		if (__carry == 0) {
  3459                 if (__carry == 0) {
  3398 		    while (__src <= __srcLastX) {
  3460                     while (__src <= __srcLastX) {
  3399 			/* copy over words */
  3461                         /* copy over words */
  3400 			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3462                         ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3401 			((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
  3463                         ((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
  3402 			__src += 8;
  3464                         __src += 8;
  3403 		    }
  3465                     }
  3404 		    while (__src <= __srcLast) {
  3466                     while (__src <= __srcLast) {
  3405 			/* copy over bytes */
  3467                         /* copy over bytes */
  3406 			__src[__ptrDelta] = __src[0];
  3468                         __src[__ptrDelta] = __src[0];
  3407 			__src ++;
  3469                         __src ++;
  3408 		    }
  3470                     }
  3409 		    goto doneSource;
  3471                     goto doneSource;
  3410 		}
  3472                 }
  3411 	    }
  3473             }
  3412 
  3474 
  3413 	    __srcLastX = __srcLastX + 4;
  3475             __srcLastX = __srcLastX + 4;
  3414 	    if (__src <= __srcLastX) {
  3476             if (__src <= __srcLastX) {
  3415 		unsigned int __sum, __digit;
  3477                 unsigned int __sum, __digit;
  3416 
  3478 
  3417 		__digit = ((unsigned *)__src)[0];
  3479                 __digit = ((unsigned *)__src)[0];
  3418 
  3480 
  3419 		asm ("addl %%eax,%%edx  \n\
  3481                 asm ("addl %%eax,%%edx  \n\
  3420 		      movl $0,%%eax     \n\
  3482                       movl $0,%%eax     \n\
  3421 		      adcl $0,%%eax"
  3483                       adcl $0,%%eax"
  3422 			: "=a"  ((unsigned long)(__carry)),
  3484                         : "=a"  ((unsigned long)(__carry)),
  3423 			  "=d"  ((unsigned long)(__sum))
  3485                           "=d"  ((unsigned long)(__sum))
  3424 			: "0"   ((unsigned long)(__carry)),
  3486                         : "0"   ((unsigned long)(__carry)),
  3425 			  "1"   (__digit) );
  3487                           "1"   (__digit) );
  3426 
  3488 
  3427 		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3489                 ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3428 		__src += 4;
  3490                 __src += 4;
  3429 
  3491 
  3430 		if (__carry == 0) {
  3492                 if (__carry == 0) {
  3431 		    while (__src <= __srcLast) {
  3493                     while (__src <= __srcLast) {
  3432 			/* copy over bytes */
  3494                         /* copy over bytes */
  3433 			__src[__ptrDelta] = __src[0];
  3495                         __src[__ptrDelta] = __src[0];
  3434 			__src ++;
  3496                         __src ++;
  3435 		    }
  3497                     }
  3436 		    goto doneSource;
  3498                     goto doneSource;
  3437 		}
  3499                 }
  3438 	    }
  3500             }
  3439 	}
  3501         }
  3440 #  endif
  3502 #  endif
  3441 # else /* not i386-GNUC */
  3503 # else /* not i386-GNUC */
  3442 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  3504 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  3443 	{
  3505         {
  3444 	    unsigned char *__srcLast4;
  3506             unsigned char *__srcLast4;
  3445 
  3507 
  3446 	    /*
  3508             /*
  3447 	     * add long-wise
  3509              * add long-wise
  3448 	     */
  3510              */
  3449 	    __srcLast4 = __srcLast - 3;
  3511             __srcLast4 = __srcLast - 3;
  3450 	    while (__src <= __srcLast4) {
  3512             while (__src <= __srcLast4) {
  3451 		unsigned int __sum;
  3513                 unsigned int __sum;
  3452 
  3514 
  3453 		__sum = ((unsigned int *)__src)[0];
  3515                 __sum = ((unsigned int *)__src)[0];
  3454 		asm {
  3516                 asm {
  3455 		      mov eax, __sum
  3517                       mov eax, __sum
  3456 		      add eax, __carry
  3518                       add eax, __carry
  3457 		      mov edx, 0
  3519                       mov edx, 0
  3458 		      adc edx, 0
  3520                       adc edx, 0
  3459 		      mov __sum, eax
  3521                       mov __sum, eax
  3460 		      mov __carry, edx
  3522                       mov __carry, edx
  3461 		    }
  3523                     }
  3462 
  3524 
  3463 		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3525                 ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
  3464 		__src += 4;
  3526                 __src += 4;
  3465 		if (__carry == 0) {
  3527                 if (__carry == 0) {
  3466 		    while (__src <= __srcLast4) {
  3528                     while (__src <= __srcLast4) {
  3467 			/* copy over words */
  3529                         /* copy over words */
  3468 			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3530                         ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3469 			__src += 4;
  3531                         __src += 4;
  3470 		    }
  3532                     }
  3471 		    while (__src <= __srcLast) {
  3533                     while (__src <= __srcLast) {
  3472 			/* copy over bytes */
  3534                         /* copy over bytes */
  3473 			__src[__ptrDelta] = __src[0];
  3535                         __src[__ptrDelta] = __src[0];
  3474 			__src ++;
  3536                         __src ++;
  3475 		    }
  3537                     }
  3476 		    goto doneSource;
  3538                     goto doneSource;
  3477 		}
  3539                 }
  3478 	    }
  3540             }
  3479 	}
  3541         }
  3480 #  else /* not i386-WIN32 */
  3542 #  else /* not i386-WIN32 */
  3481 #   if defined(__LSBFIRST__) && (__POINTER_SIZE__ == 8)
  3543 #   if defined(__LSBFIRST__) && (__POINTER_SIZE__ == 8)
  3482 	{
  3544         {
  3483 	    unsigned char *__srcLast4;
  3545             unsigned char *__srcLast4;
  3484 
  3546 
  3485 	    /*
  3547             /*
  3486 	     * add long-wise
  3548              * add long-wise
  3487 	     */
  3549              */
  3488 	    __srcLast4 = __srcLast - 3;
  3550             __srcLast4 = __srcLast - 3;
  3489 	    while (__src <= __srcLast4) {
  3551             while (__src <= __srcLast4) {
  3490 		unsigned INT __sum;
  3552                 unsigned INT __sum;
  3491 
  3553 
  3492 		__sum = ((unsigned int *)__src)[0] + __carry;
  3554                 __sum = ((unsigned int *)__src)[0] + __carry;
  3493 		((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
  3555                 ((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
  3494 		__src += 4;
  3556                 __src += 4;
  3495 		__carry = __sum >> 32;
  3557                 __carry = __sum >> 32;
  3496 		if (__carry == 0) {
  3558                 if (__carry == 0) {
  3497 		    while (__src <= __srcLast4) {
  3559                     while (__src <= __srcLast4) {
  3498 			/* copy over words */
  3560                         /* copy over words */
  3499 			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3561                         ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
  3500 			__src += 4;
  3562                         __src += 4;
  3501 		    }
  3563                     }
  3502 		    while (__src <= __srcLast) {
  3564                     while (__src <= __srcLast) {
  3503 			/* copy over bytes */
  3565                         /* copy over bytes */
  3504 			__src[__ptrDelta] = __src[0];
  3566                         __src[__ptrDelta] = __src[0];
  3505 			__src ++;
  3567                         __src ++;
  3506 		    }
  3568                     }
  3507 		    goto doneSource;
  3569                     goto doneSource;
  3508 		}
  3570                 }
  3509 	    }
  3571             }
  3510 	}
  3572         }
  3511 #   endif /* LSB+64bit */
  3573 #   endif /* LSB+64bit */
  3512 #  endif /* __i386__ & WIN32 */
  3574 #  endif /* __i386__ & WIN32 */
  3513 # endif /* __i386__ & GNUC */
  3575 # endif /* __i386__ & GNUC */
  3514 
  3576 
  3515 	/*
  3577         /*
  3516 	 * add short-wise
  3578          * add short-wise
  3517 	 */
  3579          */
  3518 	while (__src < __srcLast) {
  3580         while (__src < __srcLast) {
  3519 	    __carry += ((unsigned short *)__src)[0];
  3581             __carry += ((unsigned short *)__src)[0];
  3520 	    ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
  3582             ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
  3521 	    __carry >>= 16;
  3583             __carry >>= 16;
  3522 	    __src += 2;
  3584             __src += 2;
  3523 	}
  3585         }
  3524 	/*
  3586         /*
  3525 	 * last (odd) byte
  3587          * last (odd) byte
  3526 	 */
  3588          */
  3527 	if (__src <= __srcLast) {
  3589         if (__src <= __srcLast) {
  3528 	    __carry += __src[0];
  3590             __carry += __src[0];
  3529 	    __src[__ptrDelta] = __carry /* & 0xFF */;
  3591             __src[__ptrDelta] = __carry /* & 0xFF */;
  3530 	    __carry >>= 8;
  3592             __carry >>= 8;
  3531 	    __src++;
  3593             __src++;
  3532 	}
  3594         }
  3533 #else /* not __LSBFIRST__ */
  3595 #else /* not __LSBFIRST__ */
  3534 
  3596 
  3535 	/*
  3597         /*
  3536 	 * add byte-wise
  3598          * add byte-wise
  3537 	 */
  3599          */
  3538 	while (__src <= __srcLast) {
  3600         while (__src <= __srcLast) {
  3539 	    __carry += __src[0];
  3601             __carry += __src[0];
  3540 	    __src[__ptrDelta] = __carry /* & 0xFF */;
  3602             __src[__ptrDelta] = __carry /* & 0xFF */;
  3541 	    __src++;
  3603             __src++;
  3542 	    __carry >>= 8;
  3604             __carry >>= 8;
  3543 
  3605 
  3544 	    if (__carry == 0) {
  3606             if (__carry == 0) {
  3545 		while (__src <= __srcLast) {
  3607                 while (__src <= __srcLast) {
  3546 		    /* copy over rest */
  3608                     /* copy over rest */
  3547 		    __src[__ptrDelta] = __src[0];
  3609                     __src[__ptrDelta] = __src[0];
  3548 		    __src++;
  3610                     __src++;
  3549 		}
  3611                 }
  3550 		goto doneSource;
  3612                 goto doneSource;
  3551 	    }
  3613             }
  3552 	}
  3614         }
  3553 #endif /* __LSBFIRST__ */
  3615 #endif /* __LSBFIRST__ */
  3554 
  3616 
  3555     doneSource: ;
  3617     doneSource: ;
  3556 	/*
  3618         /*
  3557 	 * now, at most one other byte is to be stored ...
  3619          * now, at most one other byte is to be stored ...
  3558 	 */
  3620          */
  3559 	if (__len < __rsltLen) {
  3621         if (__len < __rsltLen) {
  3560 	    __src[__ptrDelta] = __carry /* & 0xFF */;
  3622             __src[__ptrDelta] = __carry /* & 0xFF */;
  3561 	    __src++;
  3623             __src++;
  3562 	}
  3624         }
  3563 
  3625 
  3564 	if (__src[__ptrDelta-1]) {      /* lastDigit */
  3626         if (__src[__ptrDelta-1]) {      /* lastDigit */
  3565 	    RETURN (result);
  3627             RETURN (result);
  3566 	}
  3628         }
  3567 	ok = true;
  3629         ok = true;
  3568     }
  3630     }
  3569 %}.
  3631 %}.
  3570 
  3632 
  3571     ok ~~ true ifTrue:[
  3633     ok ~~ true ifTrue:[
  3572 	index := 1.
  3634         index := 1.
  3573 	carry := aSmallInteger abs.
  3635         carry := aSmallInteger abs.
  3574 
  3636 
  3575 	[carry ~~ 0] whileTrue:[
  3637         [carry ~~ 0] whileTrue:[
  3576 	    (index <= len) ifTrue:[
  3638             (index <= len) ifTrue:[
  3577 		carry := (digitByteArray basicAt:index) + carry.
  3639                 carry := (digitByteArray basicAt:index) + carry.
  3578 	    ].
  3640             ].
  3579 	    resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
  3641             resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
  3580 	    carry := carry bitShift:-8.
  3642             carry := carry bitShift:-8.
  3581 	    index := index + 1
  3643             index := index + 1
  3582 	].
  3644         ].
  3583 
  3645 
  3584 	(index <= rsltLen) ifTrue:[
  3646         (index <= rsltLen) ifTrue:[
  3585 	    [index <= len] whileTrue:[
  3647             [index <= len] whileTrue:[
  3586 		resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
  3648                 resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
  3587 		index := index + 1
  3649                 index := index + 1
  3588 	    ].
  3650             ].
  3589 	    lastDigit := 0.
  3651             lastDigit := 0.
  3590 	].
  3652         ].
  3591 
  3653 
  3592 	(lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
  3654         (lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
  3593 	    ^ result
  3655             ^ result
  3594 	].
  3656         ].
  3595     ].
  3657     ].
  3596 
  3658 
  3597     ^ result compressed
  3659     ^ result compressed
  3598 
  3660 
  3599     "Modified: 24.3.1997 / 21:32:41 / cg"
  3661     "Modified: 24.3.1997 / 21:32:41 / cg"
  3611 
  3673 
  3612 %{  /* NOCONTEXT */
  3674 %{  /* NOCONTEXT */
  3613 #if defined(__LSBFIRST__)
  3675 #if defined(__LSBFIRST__)
  3614     if (__isByteArray(__INST(digitByteArray))
  3676     if (__isByteArray(__INST(digitByteArray))
  3615      && __isLargeInteger(aLargeInteger)) {
  3677      && __isLargeInteger(aLargeInteger)) {
  3616 	OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  3678         OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  3617 
  3679 
  3618 	if (__isByteArray(_otherDigitByteArray)) {
  3680         if (__isByteArray(_otherDigitByteArray)) {
  3619 	    unsigned char *_myDigits = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3681             unsigned char *_myDigits = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3620 	    unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  3682             unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  3621 	    INT _myLen = __byteArraySize(__INST(digitByteArray));
  3683             INT _myLen = __byteArraySize(__INST(digitByteArray));
  3622 
  3684             INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3623 	    if (_myLen == __POINTER_SIZE__) {
  3685 
  3624 		INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3686             if (_myLen == __POINTER_SIZE__) {
  3625 
  3687                 if (_otherLen == __POINTER_SIZE__) {
  3626 		if (_otherLen == __POINTER_SIZE__) {
  3688                     unsigned INT _myVal = *((unsigned INT *)_myDigits);
  3627 		    unsigned INT _myVal = *((unsigned INT *)_myDigits);
  3689                     unsigned INT _otherVal = *((unsigned INT *)_otherDigits);
  3628 		    unsigned INT _otherVal = *((unsigned INT *)_otherDigits);
  3690                     RETURN( (_myVal < _otherVal) ? true : false );
  3629 		    RETURN( (_myVal < _otherVal) ? true : false );
  3691                 }
  3630 		}
  3692             }
  3631 	    }
       
  3632 # if defined(UINT64) && (__POINTER_SIZE__ != 8)
  3693 # if defined(UINT64) && (__POINTER_SIZE__ != 8)
  3633 	    if (_myLen == __POINTER_SIZE__) {
  3694             if (_myLen == __POINTER_SIZE__) {
  3634 		INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3695                 if (_otherLen <= 8) {
  3635 
  3696                     UINT64 _myVal = (UINT64)(*((UINT *)_myDigits));
  3636 		if (_otherLen <= 8) {
  3697                     UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3637 		    UINT64 _myVal = (UINT64)(*((UINT *)_myDigits));
  3698                     RETURN( (_myVal < _otherVal) ? true : false );
  3638 		    UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3699                 }
  3639 		    RETURN( (_myVal < _otherVal) ? true : false );
  3700             } else {
  3640 		}
  3701                 if (_myLen <= 8) {
  3641 	    } else {
  3702                     if (_otherLen <= 8) {
  3642 		if (_myLen <= 8) {
  3703                         UINT64 _myVal = (*((UINT64 *)_myDigits));
  3643 		    INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3704                         UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3644 
  3705                         RETURN( (_myVal < _otherVal) ? true : false );
  3645 		    if (_otherLen <= 8) {
  3706                     }
  3646 			UINT64 _myVal = (*((UINT64 *)_myDigits));
  3707                     if (_otherLen == __POINTER_SIZE__) {
  3647 			UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3708                         UINT64 _myVal = (*((UINT64 *)_myDigits));
  3648 			RETURN( (_myVal < _otherVal) ? true : false );
  3709                         UINT64 _otherVal = (UINT64) *((UINT *)_otherDigits);
  3649 		    }
  3710                         RETURN( (_myVal < _otherVal) ? true : false );
  3650 		    if (_otherLen == __POINTER_SIZE__) {
  3711                     }
  3651 			UINT64 _myVal = (*((UINT64 *)_myDigits));
  3712                 }
  3652 			UINT64 _otherVal = (UINT64) *((UINT *)_otherDigits);
  3713             }
  3653 			RETURN( (_myVal < _otherVal) ? true : false );
       
  3654 		    }
       
  3655 		}
       
  3656 	    }
       
  3657 # endif /* UINT64 */
  3714 # endif /* UINT64 */
  3658 	}
  3715             while ((_myLen > 0) && (_myDigits[_myLen-1] == 0)) _myLen--;
       
  3716             while ((_otherLen > 0) && (_otherDigits[_otherLen-1] == 0)) _otherLen--;
       
  3717             if (_myLen < _otherLen) { RETURN( true ); }
       
  3718             if (_myLen > _otherLen) { RETURN (false ); }
       
  3719             while (_myLen-- > 0) {
       
  3720                 unsigned char _d1 = _myDigits[_myLen];
       
  3721                 unsigned char _d2 = _otherDigits[_myLen];
       
  3722                 
       
  3723                 if (_d1 != _d2) {
       
  3724                     if (_d1 < _d2) { RETURN( true ); }
       
  3725                     RETURN (false );
       
  3726                 }
       
  3727             }
       
  3728             RETURN (false );
       
  3729         }
  3659     }
  3730     }
  3660 #endif /* LSBFIRST */
  3731 #endif /* LSBFIRST */
  3661 %}.
  3732 %}.
  3662 
  3733 
  3663     myLen := digitByteArray size.
  3734     myLen := digitByteArray size.
  3668     "/ when properly normalized;
  3739     "/ when properly normalized;
  3669     "/ but we are tolerant here, to allow for unnormalized
  3740     "/ but we are tolerant here, to allow for unnormalized
  3670     "/ numbers to be compared ...
  3741     "/ numbers to be compared ...
  3671 
  3742 
  3672     [myLen > 0 and:[(digitByteArray basicAt:myLen) == 0]] whileTrue:[
  3743     [myLen > 0 and:[(digitByteArray basicAt:myLen) == 0]] whileTrue:[
  3673 	myLen := myLen - 1
  3744         myLen := myLen - 1
  3674     ].
  3745     ].
  3675     [otherLen > 0 and:[(otherDigitByteArray basicAt:otherLen) == 0]] whileTrue:[
  3746     [otherLen > 0 and:[(otherDigitByteArray basicAt:otherLen) == 0]] whileTrue:[
  3676 	otherLen := otherLen - 1
  3747         otherLen := otherLen - 1
  3677     ].
  3748     ].
  3678     (myLen < otherLen) ifTrue:[^ true].
  3749     (myLen < otherLen) ifTrue:[^ true].
  3679     (myLen > otherLen) ifTrue:[^ false].
  3750     (myLen > otherLen) ifTrue:[^ false].
  3680 
  3751 
  3681     [myLen > 0] whileTrue:[
  3752     [myLen > 0] whileTrue:[
  3682 	d1 := digitByteArray basicAt:myLen.
  3753         d1 := digitByteArray basicAt:myLen.
  3683 	d2 := otherDigitByteArray basicAt:myLen.
  3754         d2 := otherDigitByteArray basicAt:myLen.
  3684 	d1 == d2 ifFalse:[
  3755         d1 == d2 ifFalse:[
  3685 	    (d1 < d2) ifTrue:[^ true].
  3756             (d1 < d2) ifTrue:[^ true].
  3686 	    ^ false
  3757             ^ false
  3687 	].
  3758         ].
  3688 	myLen := myLen - 1
  3759         myLen := myLen - 1
  3689     ].
  3760     ].
  3690     ^ false
  3761     ^ false
  3691 
  3762 
  3692     "
  3763     "
  3693      |a b|
  3764      |a b|
  3726 
  3797 
  3727 %{  /* NOCONTEXT */
  3798 %{  /* NOCONTEXT */
  3728 #if defined(__LSBFIRST__)
  3799 #if defined(__LSBFIRST__)
  3729     if (__isByteArray(__INST(digitByteArray))
  3800     if (__isByteArray(__INST(digitByteArray))
  3730      && __isLargeInteger(aLargeInteger)) {
  3801      && __isLargeInteger(aLargeInteger)) {
  3731 	OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  3802         OBJ _otherDigitByteArray = __LargeIntegerInstPtr(aLargeInteger)->l_digits;
  3732 
  3803 
  3733 	if (__isByteArray(_otherDigitByteArray)) {
  3804         if (__isByteArray(_otherDigitByteArray)) {
  3734 	    unsigned char *_myDigits = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3805             unsigned char *_myDigits = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
  3735 	    unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  3806             unsigned char *_otherDigits = __ByteArrayInstPtr(_otherDigitByteArray)->ba_element;
  3736 	    INT _myLen = __byteArraySize(__INST(digitByteArray));
  3807             INT _myLen = __byteArraySize(__INST(digitByteArray));
  3737 
  3808 
  3738 	    if (_myLen == __POINTER_SIZE__) {
  3809             if (_myLen == __POINTER_SIZE__) {
  3739 		INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3810                 INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3740 
  3811 
  3741 		if (_otherLen == __POINTER_SIZE__) {
  3812                 if (_otherLen == __POINTER_SIZE__) {
  3742 		    unsigned INT _myVal = *((unsigned INT *)_myDigits);
  3813                     unsigned INT _myVal = *((unsigned INT *)_myDigits);
  3743 		    unsigned INT _otherVal = *((unsigned INT *)_otherDigits);
  3814                     unsigned INT _otherVal = *((unsigned INT *)_otherDigits);
  3744 		    RETURN( (_myVal <= _otherVal) ? true : false );
  3815                     RETURN( (_myVal <= _otherVal) ? true : false );
  3745 		}
  3816                 }
  3746 	    }
  3817             }
  3747 # if defined(UINT64) && (__POINTER_SIZE__ != 8)
  3818 # if defined(UINT64) && (__POINTER_SIZE__ != 8)
  3748 	    if (_myLen == __POINTER_SIZE__) {
  3819             if (_myLen == __POINTER_SIZE__) {
  3749 		INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3820                 INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3750 
  3821 
  3751 		if (_otherLen <= 8) {
  3822                 if (_otherLen <= 8) {
  3752 		    UINT64 _myVal = (UINT64)(*((UINT *)_myDigits));
  3823                     UINT64 _myVal = (UINT64)(*((UINT *)_myDigits));
  3753 		    UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3824                     UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3754 		    RETURN( (_myVal <= _otherVal) ? true : false );
  3825                     RETURN( (_myVal <= _otherVal) ? true : false );
  3755 		}
  3826                 }
  3756 	    } else {
  3827             } else {
  3757 		if (_myLen <= 8) {
  3828                 if (_myLen <= 8) {
  3758 		    INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3829                     INT _otherLen = __byteArraySize(_otherDigitByteArray);
  3759 
  3830 
  3760 		    if (_otherLen <= 8) {
  3831                     if (_otherLen <= 8) {
  3761 			UINT64 _myVal = (*((UINT64 *)_myDigits));
  3832                         UINT64 _myVal = (*((UINT64 *)_myDigits));
  3762 			UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3833                         UINT64 _otherVal = *((UINT64 *)_otherDigits);
  3763 			RETURN( (_myVal <= _otherVal) ? true : false );
  3834                         RETURN( (_myVal <= _otherVal) ? true : false );
  3764 		    }
  3835                     }
  3765 		    if (_otherLen == __POINTER_SIZE__) {
  3836                     if (_otherLen == __POINTER_SIZE__) {
  3766 			UINT64 _myVal = (*((UINT64 *)_myDigits));
  3837                         UINT64 _myVal = (*((UINT64 *)_myDigits));
  3767 			UINT64 _otherVal = (UINT64) *((UINT *)_otherDigits);
  3838                         UINT64 _otherVal = (UINT64) *((UINT *)_otherDigits);
  3768 			RETURN( (_myVal <= _otherVal) ? true : false );
  3839                         RETURN( (_myVal <= _otherVal) ? true : false );
  3769 		    }
  3840                     }
  3770 		}
  3841                 }
  3771 	    }
  3842             }
  3772 # endif /* UINT64 */
  3843 # endif /* UINT64 */
  3773 	}
  3844         }
  3774     }
  3845     }
  3775 #endif /* LSBFIRST */
  3846 #endif /* LSBFIRST */
  3776 %}.
  3847 %}.
  3777 
  3848 
  3778     myLen := digitByteArray size.
  3849     myLen := digitByteArray size.
  3783     "/ when properly normalized;
  3854     "/ when properly normalized;
  3784     "/ but we are tolerant here, to allow for unnormalized
  3855     "/ but we are tolerant here, to allow for unnormalized
  3785     "/ numbers to be compared ...
  3856     "/ numbers to be compared ...
  3786 
  3857 
  3787     [(digitByteArray basicAt:myLen) == 0] whileTrue:[
  3858     [(digitByteArray basicAt:myLen) == 0] whileTrue:[
  3788 	myLen := myLen - 1
  3859         myLen := myLen - 1
  3789     ].
  3860     ].
  3790     [(otherDigitByteArray basicAt:otherLen) == 0] whileTrue:[
  3861     [(otherDigitByteArray basicAt:otherLen) == 0] whileTrue:[
  3791 	otherLen := otherLen - 1
  3862         otherLen := otherLen - 1
  3792     ].
  3863     ].
  3793     (myLen < otherLen) ifTrue:[^ true].
  3864     (myLen < otherLen) ifTrue:[^ true].
  3794     (myLen > otherLen) ifTrue:[^ false].
  3865     (myLen > otherLen) ifTrue:[^ false].
  3795 
  3866 
  3796     [myLen > 0] whileTrue:[
  3867     [myLen > 0] whileTrue:[
  3797 	d1 := digitByteArray basicAt:myLen.
  3868         d1 := digitByteArray basicAt:myLen.
  3798 	d2 := otherDigitByteArray basicAt:myLen.
  3869         d2 := otherDigitByteArray basicAt:myLen.
  3799 	d1 == d2 ifFalse:[
  3870         d1 == d2 ifFalse:[
  3800 	    (d1 < d2) ifTrue:[^ true].
  3871             (d1 < d2) ifTrue:[^ true].
  3801 	    ^ false.
  3872             ^ false.
  3802 	].
  3873         ].
  3803 	myLen := myLen - 1
  3874         myLen := myLen - 1
  3804     ].
  3875     ].
  3805     ^ true
  3876     ^ true
  3806 
  3877 
  3807     "Created: / 13.2.1998 / 12:19:45 / stefan"
  3878     "Created: / 13.2.1998 / 12:19:45 / stefan"
  3808     "Modified: / 30.4.1999 / 12:46:31 / stefan"
  3879     "Modified: / 30.4.1999 / 12:46:31 / stefan"
  4526 %{
  4597 %{
  4527     OBJ _digitByteArray = __INST(digitByteArray);
  4598     OBJ _digitByteArray = __INST(digitByteArray);
  4528 
  4599 
  4529     if (__isByteArray(_digitByteArray)
  4600     if (__isByteArray(_digitByteArray)
  4530      && __isByteArray(otherDigitByteArray)) {
  4601      && __isByteArray(otherDigitByteArray)) {
  4531 	int _len1, _len2, _newLen;
  4602         int _len1, _len2, _newLen;
  4532 	unsigned char *_myDigits, *_otherDigits, *_newDigits;
  4603         unsigned char *_myDigits, *_otherDigits, *_newDigits;
  4533 	int _index, _carry;
  4604         int _index, _carry;
  4534 	int _comLen;
  4605         int _comLen;
  4535 
  4606 
  4536 	_len1 = __byteArraySize(_digitByteArray);
  4607         _len1 = __byteArraySize(_digitByteArray);
  4537 	_len2 = __byteArraySize(otherDigitByteArray);
  4608         _len2 = __byteArraySize(otherDigitByteArray);
  4538 
  4609 
  4539 	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  4610         _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  4540 	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  4611         _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  4541 
  4612 
  4542 	if (_len1 < _len2) {
  4613         if (_len1 < _len2) {
  4543 	    _comLen = _len1;
  4614             _comLen = _len1;
  4544 	    _newLen = _len2;
  4615             _newLen = _len2;
  4545 	    if (_otherDigits[_len2 - 1] == 0xFF) _newLen++;
  4616             if (_otherDigits[_len2 - 1] == 0xFF) _newLen++;
  4546 	} else if (_len2 < _len1) {
  4617         } else if (_len2 < _len1) {
  4547 	    _comLen = _len2;
  4618             _comLen = _len2;
  4548 	    _newLen = _len1;
  4619             _newLen = _len1;
  4549 	    if (_myDigits[_len1 - 1] == 0xFF) _newLen++;
  4620             if (_myDigits[_len1 - 1] == 0xFF) _newLen++;
  4550 	} else {
  4621         } else {
  4551 	    /*
  4622             /*
  4552 	     * there can only be an overflow from the high bytes,
  4623              * there can only be an overflow from the high bytes,
  4553 	     * if their sum is >= 255
  4624              * if their sum is >= 255
  4554 	     * (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)
  4555 	     */
  4626              */
  4556 	    _newLen = _len1;
  4627             _newLen = _len1;
  4557 	    if ((_otherDigits[_len2 - 1] + _myDigits[_len1 - 1]) >= 0xFF) {
  4628             if ((_otherDigits[_len2 - 1] + _myDigits[_len1 - 1]) >= 0xFF) {
  4558 		_newLen++;
  4629                 _newLen++;
  4559 	    } else {
  4630             } else {
  4560 		if (_newLen == sizeof(INT)) {
  4631                 if (_newLen == sizeof(INT)) {
  4561 		    OBJ _uint;
  4632                     OBJ _uint;
  4562 
  4633 
  4563 		    /*
  4634                     /*
  4564 		     * two word-sized numbers, no carry - a very common case ...
  4635                      * two word-sized numbers, no carry - a very common case ...
  4565 		     */
  4636                      */
  4566 #if defined(__LSB_FIRST__)
  4637 #if defined(__LSB_FIRST__)
  4567 		    unsigned INT _sum = *(unsigned INT *)_otherDigits + *(unsigned INT *)_myDigits;
  4638                     unsigned INT _sum = *(unsigned INT *)_otherDigits + *(unsigned INT *)_myDigits;
  4568 #else
  4639 #else
  4569 		    unsigned INT _sum = __unsignedLongIntVal(self) + __unsignedLongIntVal(aLargeInteger);
  4640                     unsigned INT _sum = __unsignedLongIntVal(self) + __unsignedLongIntVal(aLargeInteger);
  4570 #endif /* not LSB_FIRST */
  4641 #endif /* not LSB_FIRST */
  4571 		    if (_sum <= _MAX_INT) {
  4642                     if (_sum <= _MAX_INT) {
  4572 			_uint = __mkSmallInteger(_sum * __intVal(newSign));
  4643                         _uint = __mkSmallInteger(_sum * __intVal(newSign));
  4573 		    } else {
  4644                     } else {
  4574 			_uint = __MKULARGEINT(_sum);
  4645                         _uint = __MKULARGEINT(_sum);
  4575 			__LargeIntegerInstPtr(_uint)->l_sign = newSign;
  4646                         __LargeIntegerInstPtr(_uint)->l_sign = newSign;
  4576 		    }
  4647                     }
  4577 		    RETURN (_uint);
  4648                     RETURN (_uint);
  4578 		}
  4649                 }
  4579 	    }
  4650             }
  4580 	    _comLen = _len1;
  4651             _comLen = _len1;
  4581 	}
  4652         }
  4582 	resultDigitByteArray = __BYTEARRAY_UNINITIALIZED_NEW_INT(_newLen);
  4653         resultDigitByteArray = __BYTEARRAY_UNINITIALIZED_NEW_INT(_newLen);
  4583 
  4654 
  4584 	/*
  4655         /*
  4585 	 * must refetch - GC could have been invoked
  4656          * must refetch - GC could have been invoked
  4586 	 */
  4657          */
  4587 	_digitByteArray = __INST(digitByteArray);
  4658         _digitByteArray = __INST(digitByteArray);
  4588 
  4659 
  4589 	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  4660         _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  4590 	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  4661         _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  4591 	_newDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  4662         _newDigits = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
  4592 
  4663 
  4593 	/*
  4664         /*
  4594 	 * add them ...
  4665          * add them ...
  4595 	 */
  4666          */
  4596 	_index = 1;
  4667         _index = 1;
  4597 	_carry = 0;
  4668         _carry = 0;
  4598 
  4669 
  4599 #if defined(__LSBFIRST__)
  4670 #if defined(__LSBFIRST__)
  4600 # if (__POINTER_SIZE__ == 8) && defined(__GNUC__)
  4671 # if (__POINTER_SIZE__ == 8) && defined(__GNUC__)
  4601 #  if 0  /* not faster (on alpha) */
  4672 #  if 0  /* not faster (on alpha) */
  4602 	{
  4673         {
  4603 	    int _comLen7;
  4674             int _comLen7;
  4604 
  4675 
  4605 	    /*
  4676             /*
  4606 	     * have a 64bit integers;
  4677              * have a 64bit integers;
  4607 	     * add quad-wise
  4678              * add quad-wise
  4608 	     * accessing bytes at: [index-1][index][index+1]..[index+6]
  4679              * accessing bytes at: [index-1][index][index+1]..[index+6]
  4609 	     */
  4680              */
  4610 	    _comLen7 = _comLen - 3 - 4;
  4681             _comLen7 = _comLen - 3 - 4;
  4611 	    while (_index <= _comLen7) {
  4682             while (_index <= _comLen7) {
  4612 		UINT64 _sum, _t1, _t2;
  4683                 UINT64 _sum, _t1, _t2;
  4613 
  4684 
  4614 		asm ("addq   %5,%6,%1         /* sum */                  \n\
  4685                 asm ("addq   %5,%6,%1         /* sum */                  \n\
  4615 		      addq   %0,%1,%1         /* plus carryIn */         \n\
  4686                       addq   %0,%1,%1         /* plus carryIn */         \n\
  4616 		      cmpult %1,%5,%2         /* was there a carry ? */  \n\
  4687                       cmpult %1,%5,%2         /* was there a carry ? */  \n\
  4617 		      cmpult %1,%6,%3         /* was there a carry ? */  \n\
  4688                       cmpult %1,%6,%3         /* was there a carry ? */  \n\
  4618 		      bis    %2,%3,%0         /* carryOut */             \n\
  4689                       bis    %2,%3,%0         /* carryOut */             \n\
  4619 		     "
  4690                      "
  4620 			: "=r"  (_carry),
  4691                         : "=r"  (_carry),
  4621 			  "=r"  (_sum),
  4692                           "=r"  (_sum),
  4622 			  "r"   (_t1),
  4693                           "r"   (_t1),
  4623 			  "r"   (_t2)
  4694                           "r"   (_t2)
  4624 			: "r"   (_carry),
  4695                         : "r"   (_carry),
  4625 			  "r"   (((unsigned long *)(&(_myDigits[_index - 1])))[0]),
  4696                           "r"   (((unsigned long *)(&(_myDigits[_index - 1])))[0]),
  4626 			  "r"   (((unsigned long *)(&(_otherDigits[_index - 1])))[0])
  4697                           "r"   (((unsigned long *)(&(_otherDigits[_index - 1])))[0])
  4627 		    );
  4698                     );
  4628 		/* _sum = _sum & 0xFFFFFFFF; */
  4699                 /* _sum = _sum & 0xFFFFFFFF; */
  4629 		((unsigned long *)(&(_newDigits[_index - 1])))[0] = _sum;
  4700                 ((unsigned long *)(&(_newDigits[_index - 1])))[0] = _sum;
  4630 		_index += 8;
  4701                 _index += 8;
  4631 	    }
  4702             }
  4632 	}
  4703         }
  4633 #  endif
  4704 #  endif
  4634 # endif /* 64bit */
  4705 # endif /* 64bit */
  4635 
  4706 
  4636 # if (__POINTER_SIZE__ == 8)
  4707 # if (__POINTER_SIZE__ == 8)
  4637 # if 0  /* not faster (on alpha) */
  4708 # if 0  /* not faster (on alpha) */
  4638 	{
  4709         {
  4639 	    int _comLen7;
  4710             int _comLen7;
  4640 
  4711 
  4641 	    /*
  4712             /*
  4642 	     * have a 64bit integers;
  4713              * have a 64bit integers;
  4643 	     * add quad-wise
  4714              * add quad-wise
  4644 	     * accessing bytes at: [index-1][index][index+1]..[index+6]
  4715              * accessing bytes at: [index-1][index][index+1]..[index+6]
  4645 	     */
  4716              */
  4646 	    _comLen7 = _comLen - 3 - 4;
  4717             _comLen7 = _comLen - 3 - 4;
  4647 	    while (_index <= _comLen7) {
  4718             while (_index <= _comLen7) {
  4648 		UINT64 _sum, _t1, _t2;
  4719                 UINT64 _sum, _t1, _t2;
  4649 
  4720 
  4650 		_t1 = ((UINT64 *)(&(_myDigits[_index - 1])))[0];
  4721                 _t1 = ((UINT64 *)(&(_myDigits[_index - 1])))[0];
  4651 		_t2 = ((UINT64 *)(&(_otherDigits[_index - 1])))[0];
  4722                 _t2 = ((UINT64 *)(&(_otherDigits[_index - 1])))[0];
  4652 		_sum = _t1 + _t2 + _carry;
  4723                 _sum = _t1 + _t2 + _carry;
  4653 		((UINT64 *)(&(_newDigits[_index - 1])))[0] = _sum;
  4724                 ((UINT64 *)(&(_newDigits[_index - 1])))[0] = _sum;
  4654 		_carry = (_sum < _t1) | (_sum < _t2);
  4725                 _carry = (_sum < _t1) | (_sum < _t2);
  4655 		_index += 8;
  4726                 _index += 8;
  4656 	    }
  4727             }
  4657 	}
  4728         }
  4658 #  endif
  4729 #  endif
  4659 # endif /* 64bit */
  4730 # endif /* 64bit */
  4660 
  4731 
  4661 # ifdef UINT64
  4732 # ifdef UINT64
  4662 	{
  4733         {
  4663 	    int _comLen3;
  4734             int _comLen3;
  4664 
  4735 
  4665 	    /*
  4736             /*
  4666 	     * have a 64bit integer type;
  4737              * have a 64bit integer type;
  4667 	     * add int-wise
  4738              * add int-wise
  4668 	     * accessing bytes at: [index-1][index][index+1][index+2]
  4739              * accessing bytes at: [index-1][index][index+1][index+2]
  4669 	     */
  4740              */
  4670 	    _comLen3 = _comLen - 3;
  4741             _comLen3 = _comLen - 3;
  4671 	    while (_index <= _comLen3) {
  4742             while (_index <= _comLen3) {
  4672 		UINT64 _sum;
  4743                 UINT64 _sum;
  4673 
  4744 
  4674 		/* do not merge the 3 lines below into one -
  4745                 /* do not merge the 3 lines below into one -
  4675 		 * (will do sign extension then, which is wrong here)
  4746                  * (will do sign extension then, which is wrong here)
  4676 		 */
  4747                  */
  4677 		_sum = (unsigned)_carry;
  4748                 _sum = (unsigned)_carry;
  4678 		_sum += ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4749                 _sum += ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4679 		_sum += ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4750                 _sum += ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4680 		_carry = _sum >> 32;
  4751                 _carry = _sum >> 32;
  4681 		/* _sum = _sum & 0xFFFFFFFF; */
  4752                 /* _sum = _sum & 0xFFFFFFFF; */
  4682 		((unsigned int *)(&(_newDigits[_index - 1])))[0] = _sum;
  4753                 ((unsigned int *)(&(_newDigits[_index - 1])))[0] = _sum;
  4683 		_index += 4;
  4754                 _index += 4;
  4684 	    }
  4755             }
  4685 	}
  4756         }
  4686 # else
  4757 # else
  4687 #  if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
  4758 #  if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
  4688 	{
  4759         {
  4689 	    int _comLen3;
  4760             int _comLen3;
  4690 
  4761 
  4691 	    _comLen3 = _comLen - 3 - 4;
  4762             _comLen3 = _comLen - 3 - 4;
  4692 	    while (_index <= _comLen3) {
  4763             while (_index <= _comLen3) {
  4693 		unsigned int _sum, _sum2;
  4764                 unsigned int _sum, _sum2;
  4694 		unsigned int __in1A, __in1B, __in2A, __in2B;
  4765                 unsigned int __in1A, __in1B, __in2A, __in2B;
  4695 
  4766 
  4696 		__in1A = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4767                 __in1A = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4697 		__in2A = ((unsigned int *)(&(_myDigits[_index - 1])))[1];
  4768                 __in2A = ((unsigned int *)(&(_myDigits[_index - 1])))[1];
  4698 		__in1B = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4769                 __in1B = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4699 		__in2B = ((unsigned int *)(&(_otherDigits[_index - 1])))[1];
  4770                 __in2B = ((unsigned int *)(&(_otherDigits[_index - 1])))[1];
  4700 
  4771 
  4701 		asm ("addl %%edx,%%eax  \n\
  4772                 asm ("addl %%edx,%%eax  \n\
  4702 		      movl $0,%%edx     \n\
  4773                       movl $0,%%edx     \n\
  4703 		      adcl $0,%%edx     \n\
  4774                       adcl $0,%%edx     \n\
  4704 		      addl %5,%%eax     \n\
  4775                       addl %5,%%eax     \n\
  4705 		      adcl $0,%%edx     \n\
  4776                       adcl $0,%%edx     \n\
  4706 					\n\
  4777                                         \n\
  4707 		      addl %%edx,%%ecx  \n\
  4778                       addl %%edx,%%ecx  \n\
  4708 		      movl $0,%%edx     \n\
  4779                       movl $0,%%edx     \n\
  4709 		      adcl $0,%%edx     \n\
  4780                       adcl $0,%%edx     \n\
  4710 		      addl %7,%%ecx     \n\
  4781                       addl %7,%%ecx     \n\
  4711 		      adcl $0,%%edx     \n\
  4782                       adcl $0,%%edx     \n\
  4712 		     "
  4783                      "
  4713 			: "=d"  (_carry),
  4784                         : "=d"  (_carry),
  4714 			  "=a"  (_sum),
  4785                           "=a"  (_sum),
  4715 			  "=c"  (_sum2)
  4786                           "=c"  (_sum2)
  4716 			: "0"   (_carry),
  4787                         : "0"   (_carry),
  4717 			  "1"   (__in1A),
  4788                           "1"   (__in1A),
  4718 			  "rm"  (__in1B),
  4789                           "rm"  (__in1B),
  4719 			  "2"   (__in2A),
  4790                           "2"   (__in2A),
  4720 			  "rm"  (__in2B)
  4791                           "rm"  (__in2B)
  4721 		    );
  4792                     );
  4722 
  4793 
  4723 		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4794                 ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4724 		((unsigned *)(&(_newDigits[_index - 1])))[1] = _sum2;
  4795                 ((unsigned *)(&(_newDigits[_index - 1])))[1] = _sum2;
  4725 		_index += 8;
  4796                 _index += 8;
  4726 	    }
  4797             }
  4727 	    /*
  4798             /*
  4728 	     * add int-wise
  4799              * add int-wise
  4729 	     * accessing bytes at: [index-1][index][index+1][index+2]
  4800              * accessing bytes at: [index-1][index][index+1][index+2]
  4730 	     */
  4801              */
  4731 	    _comLen3 = _comLen3 + 4;
  4802             _comLen3 = _comLen3 + 4;
  4732 	    if (_index <= _comLen3) {
  4803             if (_index <= _comLen3) {
  4733 		unsigned int _sum;
  4804                 unsigned int _sum;
  4734 		unsigned int __inA, __inB;
  4805                 unsigned int __inA, __inB;
  4735 
  4806 
  4736 		__inA = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4807                 __inA = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4737 		__inB = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4808                 __inB = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4738 
  4809 
  4739 		asm ("addl %%edx,%%eax      \n\
  4810                 asm ("addl %%edx,%%eax      \n\
  4740 		      movl $0,%%edx         \n\
  4811                       movl $0,%%edx         \n\
  4741 		      adcl $0,%%edx         \n\
  4812                       adcl $0,%%edx         \n\
  4742 		      addl %4,%%eax         \n\
  4813                       addl %4,%%eax         \n\
  4743 		      adcl $0,%%edx"
  4814                       adcl $0,%%edx"
  4744 			: "=d"  (_carry),
  4815                         : "=d"  (_carry),
  4745 			  "=a"  (_sum)
  4816                           "=a"  (_sum)
  4746 			: "0"   (_carry),
  4817                         : "0"   (_carry),
  4747 			  "1"   (__inA),
  4818                           "1"   (__inA),
  4748 			  "rm"  (__inB)
  4819                           "rm"  (__inB)
  4749 		    );
  4820                     );
  4750 
  4821 
  4751 		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4822                 ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4752 		_index += 4;
  4823                 _index += 4;
  4753 	    }
  4824             }
  4754 	}
  4825         }
  4755 #  endif /* __i386__ && GNUC */
  4826 #  endif /* __i386__ && GNUC */
  4756 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  4827 #  if defined(WIN32) && defined(__BORLANDC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
  4757 	{
  4828         {
  4758 	    int _comLen3;
  4829             int _comLen3;
  4759 
  4830 
  4760 	    /*
  4831             /*
  4761 	     * add long-wise
  4832              * add long-wise
  4762 	     * accessing bytes at: [index-1][index][index+1][index+2]
  4833              * accessing bytes at: [index-1][index][index+1][index+2]
  4763 	     */
  4834              */
  4764 	    _comLen3 = _comLen - 3;
  4835             _comLen3 = _comLen - 3;
  4765 	    while (_index <= _comLen3) {
  4836             while (_index <= _comLen3) {
  4766 		unsigned int _sum, _v1, _v2;
  4837                 unsigned int _sum, _v1, _v2;
  4767 
  4838 
  4768 		_v1 = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4839                 _v1 = ((unsigned int *)(&(_myDigits[_index - 1])))[0];
  4769 		_v2 = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4840                 _v2 = ((unsigned int *)(&(_otherDigits[_index - 1])))[0];
  4770 		asm {
  4841                 asm {
  4771 		      mov eax, _v1
  4842                       mov eax, _v1
  4772 		      add eax, _v2
  4843                       add eax, _v2
  4773 		      mov edx, 0
  4844                       mov edx, 0
  4774 		      adc edx, 0
  4845                       adc edx, 0
  4775 		      add eax, _carry
  4846                       add eax, _carry
  4776 		      adc edx, 0
  4847                       adc edx, 0
  4777 		      mov _carry, edx
  4848                       mov _carry, edx
  4778 		      mov _sum, eax
  4849                       mov _sum, eax
  4779 		    }
  4850                     }
  4780 
  4851 
  4781 		((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4852                 ((unsigned *)(&(_newDigits[_index - 1])))[0] = _sum;
  4782 		_index += 4;
  4853                 _index += 4;
  4783 	    }
  4854             }
  4784 	}
  4855         }
  4785 #  endif /* __i386__ && WIN32 */
  4856 #  endif /* __i386__ && WIN32 */
  4786 # endif /* INT64 */
  4857 # endif /* INT64 */
  4787 	/*
  4858         /*
  4788 	 * add short-wise
  4859          * add short-wise
  4789 	 * accessing bytes at: [index-1][index]
  4860          * accessing bytes at: [index-1][index]
  4790 	 */
  4861          */
  4791 	while (_index < _comLen) {
  4862         while (_index < _comLen) {
  4792 	    unsigned int _sum;
  4863             unsigned int _sum;
  4793 
  4864 
  4794 	    _sum = _carry
  4865             _sum = _carry
  4795 		   + ((unsigned short *)(&(_myDigits[_index - 1])))[0]
  4866                    + ((unsigned short *)(&(_myDigits[_index - 1])))[0]
  4796 		   + ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
  4867                    + ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
  4797 	    _carry = _sum >> 16;
  4868             _carry = _sum >> 16;
  4798 	    /* _sum = _sum & 0xFFFF; */
  4869             /* _sum = _sum & 0xFFFF; */
  4799 	    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4870             *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4800 	    _index += 2;
  4871             _index += 2;
  4801 	}
  4872         }
  4802 #else
  4873 #else
  4803 # ifdef __sparc__
  4874 # ifdef __sparc__
  4804 	/*
  4875         /*
  4805 	 * add short-wise
  4876          * add short-wise
  4806 	 * accessing bytes at: [index-1][index]
  4877          * accessing bytes at: [index-1][index]
  4807 	 */
  4878          */
  4808 	while (_index < _comLen) {
  4879         while (_index < _comLen) {
  4809 	    unsigned int _sum;
  4880             unsigned int _sum;
  4810 	    unsigned short _v1, _v2;
  4881             unsigned short _v1, _v2;
  4811 
  4882 
  4812 	    _v1 = ((unsigned short *)(&(_myDigits[_index - 1])))[0];
  4883             _v1 = ((unsigned short *)(&(_myDigits[_index - 1])))[0];
  4813 	    _v2 = ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
  4884             _v2 = ((unsigned short *)(&(_otherDigits[_index - 1])))[0];
  4814 	    _sum = _carry + (_v1>>8) + (_v2>>8);
  4885             _sum = _carry + (_v1>>8) + (_v2>>8);
  4815 	    _carry = _sum >> 8;
  4886             _carry = _sum >> 8;
  4816 	    _newDigits[_index - 1] = _sum;
  4887             _newDigits[_index - 1] = _sum;
  4817 
  4888 
  4818 	    _sum = _carry + (_v1 & 0xFF) + (_v2 & 0xFF);
  4889             _sum = _carry + (_v1 & 0xFF) + (_v2 & 0xFF);
  4819 	    _carry = _sum >> 8;
  4890             _carry = _sum >> 8;
  4820 	    _newDigits[_index] = _sum;
  4891             _newDigits[_index] = _sum;
  4821 	    _index += 2;
  4892             _index += 2;
  4822 	}
  4893         }
  4823 # endif
  4894 # endif
  4824 #endif /* __LSBFIRST__ */
  4895 #endif /* __LSBFIRST__ */
  4825 
  4896 
  4826 	/*
  4897         /*
  4827 	 * add byte-wise
  4898          * add byte-wise
  4828 	 */
  4899          */
  4829 	while (_index <= _comLen) {
  4900         while (_index <= _comLen) {
  4830 	    unsigned int _sum;
  4901             unsigned int _sum;
  4831 
  4902 
  4832 	    _sum = _carry
  4903             _sum = _carry
  4833 		   + _myDigits[_index - 1]
  4904                    + _myDigits[_index - 1]
  4834 		   + _otherDigits[_index - 1];
  4905                    + _otherDigits[_index - 1];
  4835 	    _carry = _sum >> 8;
  4906             _carry = _sum >> 8;
  4836 	    /* _sum = _sum & 0xFF; */
  4907             /* _sum = _sum & 0xFF; */
  4837 	    _newDigits[_index - 1] = _sum;
  4908             _newDigits[_index - 1] = _sum;
  4838 	    _index++;
  4909             _index++;
  4839 	}
  4910         }
  4840 
  4911 
  4841 	/*
  4912         /*
  4842 	 * rest
  4913          * rest
  4843 	 */
  4914          */
  4844 	if (_len1 > _len2) {
  4915         if (_len1 > _len2) {
  4845 #if defined(__LSBFIRST__)
  4916 #if defined(__LSBFIRST__)
  4846 	    if (_index <= _len1) {
  4917             if (_index <= _len1) {
  4847 		if ((_index - 1) & 1) {
  4918                 if ((_index - 1) & 1) {
  4848 		    /* odd byte */
  4919                     /* odd byte */
  4849 		    unsigned int _sum;
  4920                     unsigned int _sum;
  4850 
  4921 
  4851 		    _sum = _carry + _myDigits[_index - 1];
  4922                     _sum = _carry + _myDigits[_index - 1];
  4852 		    _carry = _sum >> 8;
  4923                     _carry = _sum >> 8;
  4853 		    /* _sum = _sum & 0xFF; */
  4924                     /* _sum = _sum & 0xFF; */
  4854 		    _newDigits[_index - 1] = _sum;
  4925                     _newDigits[_index - 1] = _sum;
  4855 		    _index++;
  4926                     _index++;
  4856 		}
  4927                 }
  4857 
  4928 
  4858 		while (_index < _len1) {
  4929                 while (_index < _len1) {
  4859 		    /* shorts */
  4930                     /* shorts */
  4860 		    unsigned int _sum;
  4931                     unsigned int _sum;
  4861 
  4932 
  4862 		    _sum = _carry + *(unsigned short *)(&(_myDigits[_index - 1]));
  4933                     _sum = _carry + *(unsigned short *)(&(_myDigits[_index - 1]));
  4863 		    _carry = _sum >> 16;
  4934                     _carry = _sum >> 16;
  4864 		    /* _sum = _sum & 0xFFFF; */
  4935                     /* _sum = _sum & 0xFFFF; */
  4865 		    *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4936                     *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4866 		    _index += 2;
  4937                     _index += 2;
  4867 		}
  4938                 }
  4868 
  4939 
  4869 		if (_index <= _len1) {
  4940                 if (_index <= _len1) {
  4870 		    /* last byte */
  4941                     /* last byte */
  4871 		    unsigned int _sum;
  4942                     unsigned int _sum;
  4872 
  4943 
  4873 		    _sum = _carry + _myDigits[_index - 1];
  4944                     _sum = _carry + _myDigits[_index - 1];
  4874 		    _carry = _sum >> 8;
  4945                     _carry = _sum >> 8;
  4875 		    /* _sum = _sum & 0xFF; */
  4946                     /* _sum = _sum & 0xFF; */
  4876 		    _newDigits[_index - 1] = _sum;
  4947                     _newDigits[_index - 1] = _sum;
  4877 		    _index++;
  4948                     _index++;
  4878 		}
  4949                 }
  4879 	    }
  4950             }
  4880 #else
  4951 #else
  4881 	    while (_index <= _len1) {
  4952             while (_index <= _len1) {
  4882 		unsigned int _sum;
  4953                 unsigned int _sum;
  4883 
  4954 
  4884 		_sum = _carry + _myDigits[_index - 1];
  4955                 _sum = _carry + _myDigits[_index - 1];
  4885 		_carry = _sum >> 8;
  4956                 _carry = _sum >> 8;
  4886 		/* _sum = _sum & 0xFF; */
  4957                 /* _sum = _sum & 0xFF; */
  4887 		_newDigits[_index - 1] = _sum;
  4958                 _newDigits[_index - 1] = _sum;
  4888 		_index++;
  4959                 _index++;
  4889 	    }
  4960             }
  4890 #endif /* not LSB */
  4961 #endif /* not LSB */
  4891 	} else {
  4962         } else {
  4892 	    if (_len2 > _len1) {
  4963             if (_len2 > _len1) {
  4893 #if defined(__LSBFIRST__)
  4964 #if defined(__LSBFIRST__)
  4894 		if (_index <= _len2) {
  4965                 if (_index <= _len2) {
  4895 		    if ((_index - 1) & 1) {
  4966                     if ((_index - 1) & 1) {
  4896 			/* odd byte */
  4967                         /* odd byte */
  4897 			unsigned int _sum;
  4968                         unsigned int _sum;
  4898 
  4969 
  4899 			_sum = _carry + _otherDigits[_index - 1];
  4970                         _sum = _carry + _otherDigits[_index - 1];
  4900 			_carry = _sum >> 8;
  4971                         _carry = _sum >> 8;
  4901 			/* _sum = _sum & 0xFF; */
  4972                         /* _sum = _sum & 0xFF; */
  4902 			_newDigits[_index - 1] = _sum;
  4973                         _newDigits[_index - 1] = _sum;
  4903 			_index++;
  4974                         _index++;
  4904 		    }
  4975                     }
  4905 
  4976 
  4906 		    while (_index < _len2) {
  4977                     while (_index < _len2) {
  4907 			/* shorts */
  4978                         /* shorts */
  4908 			unsigned int _sum;
  4979                         unsigned int _sum;
  4909 
  4980 
  4910 			_sum = _carry + *(unsigned short *)(&(_otherDigits[_index - 1]));
  4981                         _sum = _carry + *(unsigned short *)(&(_otherDigits[_index - 1]));
  4911 			_carry = _sum >> 16;
  4982                         _carry = _sum >> 16;
  4912 			/* _sum = _sum & 0xFFFF; */
  4983                         /* _sum = _sum & 0xFFFF; */
  4913 			*(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4984                         *(unsigned short *)(&(_newDigits[_index - 1])) = _sum;
  4914 			_index += 2;
  4985                         _index += 2;
  4915 		    }
  4986                     }
  4916 
  4987 
  4917 		    if (_index <= _len2) {
  4988                     if (_index <= _len2) {
  4918 			/* last byte */
  4989                         /* last byte */
  4919 			unsigned int _sum;
  4990                         unsigned int _sum;
  4920 
  4991 
  4921 			_sum = _carry + _otherDigits[_index - 1];
  4992                         _sum = _carry + _otherDigits[_index - 1];
  4922 			_carry = _sum >> 8;
  4993                         _carry = _sum >> 8;
  4923 			/* _sum = _sum & 0xFF; */
  4994                         /* _sum = _sum & 0xFF; */
  4924 			_newDigits[_index - 1] = _sum;
  4995                         _newDigits[_index - 1] = _sum;
  4925 			_index++;
  4996                         _index++;
  4926 		    }
  4997                     }
  4927 		}
  4998                 }
  4928 #else
  4999 #else
  4929 		while (_index <= _len2) {
  5000                 while (_index <= _len2) {
  4930 		    unsigned int _sum;
  5001                     unsigned int _sum;
  4931 
  5002 
  4932 		    _sum = _carry + _otherDigits[_index - 1];
  5003                     _sum = _carry + _otherDigits[_index - 1];
  4933 		    _carry = _sum >> 8;
  5004                     _carry = _sum >> 8;
  4934 		    /* _sum = _sum & 0xFF; */
  5005                     /* _sum = _sum & 0xFF; */
  4935 		    _newDigits[_index - 1] = _sum;
  5006                     _newDigits[_index - 1] = _sum;
  4936 		    _index++;
  5007                     _index++;
  4937 		}
  5008                 }
  4938 #endif /* not LSB */
  5009 #endif /* not LSB */
  4939 	    }
  5010             }
  4940 	}
  5011         }
  4941 
  5012 
  4942 	while (_index <= _newLen) {
  5013         while (_index <= _newLen) {
  4943 	    unsigned int _sum;
  5014             unsigned int _sum;
  4944 
  5015 
  4945 	    _sum = _carry;
  5016             _sum = _carry;
  4946 	    _carry = _sum >> 8;
  5017             _carry = _sum >> 8;
  4947 	    /* _sum = _sum & 0xFF; */
  5018             /* _sum = _sum & 0xFF; */
  4948 	    _newDigits[_index - 1] = _sum;
  5019             _newDigits[_index - 1] = _sum;
  4949 	    _index++;
  5020             _index++;
  4950 	}
  5021         }
  4951     }
  5022     }
  4952 %}.
  5023 %}.
  4953     resultDigitByteArray notNil ifTrue:[
  5024     resultDigitByteArray notNil ifTrue:[
  4954 	result := self class basicNew.
  5025         result := self class basicNew.
  4955 	result setDigits:resultDigitByteArray.
  5026         result setDigits:resultDigitByteArray.
  4956 	result setSign:newSign.
  5027         result setSign:newSign.
  4957     ] ifFalse:[
  5028     ] ifFalse:[
  4958 	len1 := digitByteArray size.
  5029         len1 := digitByteArray size.
  4959 	len2 := otherDigitByteArray size.
  5030         len2 := otherDigitByteArray size.
  4960 
  5031 
  4961 	"/ earlier versions estimated the newLength as:
  5032         "/ earlier versions estimated the newLength as:
  4962 	"/ (len1 max:len2) + 1
  5033         "/ (len1 max:len2) + 1
  4963 	"/ and reduced the result.
  5034         "/ and reduced the result.
  4964 	"/ however, if one of the addends is smaller,
  5035         "/ however, if one of the addends is smaller,
  4965 	"/ the result will never require another digit,
  5036         "/ the result will never require another digit,
  4966 	"/ if the highest digit of the larger addent is
  5037         "/ if the highest digit of the larger addent is
  4967 	"/ not equal to 255. Therefore, in most cases,
  5038         "/ not equal to 255. Therefore, in most cases,
  4968 	"/ we can avoid the computation and resizing
  5039         "/ we can avoid the computation and resizing
  4969 	"/ in #reduced.
  5040         "/ in #reduced.
  4970 
  5041 
  4971 	len1 < len2 ifTrue:[
  5042         len1 < len2 ifTrue:[
  4972 	    newLen := len2.
  5043             newLen := len2.
  4973 	    (otherDigitByteArray at:len2) == 16rFF ifTrue:[
  5044             (otherDigitByteArray at:len2) == 16rFF ifTrue:[
  4974 		newLen := newLen + 1
  5045                 newLen := newLen + 1
  4975 	    ]
  5046             ]
  4976 	] ifFalse:[
  5047         ] ifFalse:[
  4977 	    len2 < len1 ifTrue:[
  5048             len2 < len1 ifTrue:[
  4978 		newLen := len1.
  5049                 newLen := len1.
  4979 		(digitByteArray at:len1) == 16rFF ifTrue:[
  5050                 (digitByteArray at:len1) == 16rFF ifTrue:[
  4980 		    newLen := newLen + 1
  5051                     newLen := newLen + 1
  4981 		]
  5052                 ]
  4982 	    ] ifFalse:[
  5053             ] ifFalse:[
  4983 		newLen := len1 + 1.
  5054                 newLen := len1 + 1.
  4984 	    ]
  5055             ]
  4985 	].
  5056         ].
  4986 
  5057 
  4987 	result := self class basicNew numberOfDigits:newLen.
  5058         result := self class basicNew numberOfDigits:newLen.
  4988 	result sign:newSign.
  5059         result sign:newSign.
  4989 	resultDigitByteArray := result digitBytes.
  5060         resultDigitByteArray := result digitBytes.
  4990 
  5061 
  4991 	index := 1.
  5062         index := 1.
  4992 	carry := 0.
  5063         carry := 0.
  4993 
  5064 
  4994 	done := false.
  5065         done := false.
  4995 	[done] whileFalse:[
  5066         [done] whileFalse:[
  4996 	    sum := carry.
  5067             sum := carry.
  4997 	    (index <= len1) ifTrue:[
  5068             (index <= len1) ifTrue:[
  4998 		sum := sum + (digitByteArray basicAt:index).
  5069                 sum := sum + (digitByteArray basicAt:index).
  4999 		(index <= len2) ifTrue:[
  5070                 (index <= len2) ifTrue:[
  5000 		    sum := sum + (otherDigitByteArray basicAt:index)
  5071                     sum := sum + (otherDigitByteArray basicAt:index)
  5001 		]
  5072                 ]
  5002 	    ] ifFalse:[
  5073             ] ifFalse:[
  5003 		(index <= len2) ifTrue:[
  5074                 (index <= len2) ifTrue:[
  5004 		    sum := sum + (otherDigitByteArray basicAt:index)
  5075                     sum := sum + (otherDigitByteArray basicAt:index)
  5005 		] ifFalse:[
  5076                 ] ifFalse:[
  5006 		    "end reached"
  5077                     "end reached"
  5007 		    done := true
  5078                     done := true
  5008 		]
  5079                 ]
  5009 	    ].
  5080             ].
  5010 	    (sum >= 16r100) ifTrue:[
  5081             (sum >= 16r100) ifTrue:[
  5011 		carry := 1.
  5082                 carry := 1.
  5012 		sum := sum - 16r100
  5083                 sum := sum - 16r100
  5013 	    ] ifFalse:[
  5084             ] ifFalse:[
  5014 		carry := 0
  5085                 carry := 0
  5015 	    ].
  5086             ].
  5016 	    resultDigitByteArray basicAt:index put:sum.
  5087             resultDigitByteArray basicAt:index put:sum.
  5017 	    index := index + 1
  5088             index := index + 1
  5018 	].
  5089         ].
  5019     ].
  5090     ].
  5020 
  5091 
  5021     ^ result compressed
  5092     ^ result compressed
  5022 
  5093 
  5023     "Modified: 11.8.1997 / 03:23:37 / cg"
  5094     "Modified: 11.8.1997 / 03:23:37 / cg"
  5024 !
  5095 !
  5025 
  5096 
  5026 absSubtract:aLargeInteger
  5097 absSubtract:aLargeInteger
  5027     "private helper for division:
  5098     "private helper for division:
  5028 	destructively subtract aLargeInteger from myself
  5099         destructively subtract aLargeInteger from myself
  5029 	AND return true, if the result is non-zero, false otherwise.
  5100         AND return true, if the result is non-zero, false otherwise.
  5030 	(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
  5031 	 on the receiver)
  5102          on the receiver)
  5032 	Only allowed for positive receiver and argument
  5103         Only allowed for positive receiver and argument
  5033 	The receiver must be >= the argument.
  5104         The receiver must be >= the argument.
  5034 	The receiver must be a temporary scratch-number"
  5105         The receiver must be a temporary scratch-number"
  5035 
  5106 
  5036     |otherDigitByteArray
  5107     |otherDigitByteArray
  5037      len1   "{ Class: SmallInteger }"
  5108      len1   "{ Class: SmallInteger }"
  5038      len2   "{ Class: SmallInteger }"
  5109      len2   "{ Class: SmallInteger }"
  5039      index  "{ Class: SmallInteger }"
  5110      index  "{ Class: SmallInteger }"
  5045     notZero := false.
  5116     notZero := false.
  5046     len1 := digitByteArray size.
  5117     len1 := digitByteArray size.
  5047     otherDigitByteArray := aLargeInteger digitBytes.
  5118     otherDigitByteArray := aLargeInteger digitBytes.
  5048     len2 := otherDigitByteArray size.
  5119     len2 := otherDigitByteArray size.
  5049     len2 > len1 ifTrue:[
  5120     len2 > len1 ifTrue:[
  5050 	[(otherDigitByteArray at:len2) == 0] whileTrue:[
  5121         [(otherDigitByteArray at:len2) == 0] whileTrue:[
  5051 	    len2 := len2 - 1
  5122             len2 := len2 - 1
  5052 	].
  5123         ].
  5053 	len2 > len1 ifTrue:[
  5124         len2 > len1 ifTrue:[
  5054 	    self error:'operation failed' "/ may not be called that way
  5125             self error:'operation failed' "/ may not be called that way
  5055 	].
  5126         ].
  5056     ].
  5127     ].
  5057     "/ knowing that len2 is <= len1
  5128     "/ knowing that len2 is <= len1
  5058 %{
  5129 %{
  5059 
  5130 
  5060     OBJ _digitByteArray = __INST(digitByteArray);
  5131     OBJ _digitByteArray = __INST(digitByteArray);
  5061 
  5132 
  5062     if (__isByteArray(_digitByteArray)
  5133     if (__isByteArray(_digitByteArray)
  5063      && __isByteArray(otherDigitByteArray)) {
  5134      && __isByteArray(otherDigitByteArray)) {
  5064 	int _len1 = __intVal(len1),
  5135         int _len1 = __intVal(len1),
  5065 	    _len2 = __intVal(len2);
  5136             _len2 = __intVal(len2);
  5066 	unsigned char *_myDigits, *_otherDigits;
  5137         unsigned char *_myDigits, *_otherDigits;
  5067 	int _index = 1, _borrow = 0;
  5138         int _index = 1, _borrow = 0;
  5068 	INT _diff;
  5139         INT _diff;
  5069 	int anyBitNonZero = 0;
  5140         int anyBitNonZero = 0;
  5070 
  5141 
  5071 	_otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  5142         _otherDigits = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
  5072 	_myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  5143         _myDigits = __ByteArrayInstPtr(_digitByteArray)->ba_element;
  5073 
  5144 
  5074 #if defined(__LSBFIRST__)
  5145 #if defined(__LSBFIRST__)
  5075 # if __POINTER_SIZE__ == 8
  5146 # if __POINTER_SIZE__ == 8
  5076 	{
  5147         {
  5077 	    int _len2Q;
  5148             int _len2Q;
  5078 	    /*
  5149             /*
  5079 	     * subtract int-wise
  5150              * subtract int-wise
  5080 	     */
  5151              */
  5081 	    _len2Q = _len2-2;
  5152             _len2Q = _len2-2;
  5082 	    while (_index < _len2Q) {
  5153             while (_index < _len2Q) {
  5083 		/* 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 */
  5084 		_diff = ((unsigned int *)(_myDigits+_index-1))[0];
  5155                 _diff = ((unsigned int *)(_myDigits+_index-1))[0];
  5085 		_diff -= ((unsigned int *)(_otherDigits+_index-1))[0];
  5156                 _diff -= ((unsigned int *)(_otherDigits+_index-1))[0];
  5086 		_diff -= _borrow;
  5157                 _diff -= _borrow;
  5087 		if (_diff >= 0) {
  5158                 if (_diff >= 0) {
  5088 		    _borrow = 0;
  5159                     _borrow = 0;
  5089 		} else {
  5160                 } else {
  5090 		    _borrow = 1;
  5161                     _borrow = 1;
  5091 		    /* _diff += 0x10000; */
  5162                     /* _diff += 0x10000; */
  5092 		}
  5163                 }
  5093 		((unsigned int *)(_myDigits+_index-1))[0] = _diff;
  5164                 ((unsigned int *)(_myDigits+_index-1))[0] = _diff;
  5094 		anyBitNonZero |= (_diff & 0xFFFFFFFFL);
  5165                 anyBitNonZero |= (_diff & 0xFFFFFFFFL);
  5095 		_index += 4;
  5166                 _index += 4;
  5096 	    }
  5167             }
  5097 	}
  5168         }
  5098 # endif
  5169 # endif
  5099 
  5170 
  5100 	/*
  5171         /*
  5101 	 * subtract short-wise
  5172          * subtract short-wise
  5102 	 */
  5173          */
  5103 	while (_index < _len2) {
  5174         while (_index < _len2) {
  5104 	    /* 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 */
  5105 	    _diff = ((unsigned short *)(_myDigits+_index-1))[0];
  5176             _diff = ((unsigned short *)(_myDigits+_index-1))[0];
  5106 	    _diff -= ((unsigned short *)(_otherDigits+_index-1))[0];
  5177             _diff -= ((unsigned short *)(_otherDigits+_index-1))[0];
  5107 	    _diff -= _borrow;
  5178             _diff -= _borrow;
  5108 	    if (_diff >= 0) {
  5179             if (_diff >= 0) {
  5109 		_borrow = 0;
  5180                 _borrow = 0;
  5110 	    } else {
  5181             } else {
  5111 		_borrow = 1;
  5182                 _borrow = 1;
  5112 		/* _diff += 0x10000; */
  5183                 /* _diff += 0x10000; */
  5113 	    }
  5184             }
  5114 	    ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5185             ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5115 	    anyBitNonZero |= (_diff & 0xFFFF);
  5186             anyBitNonZero |= (_diff & 0xFFFF);
  5116 	    _index += 2;
  5187             _index += 2;
  5117 	}
  5188         }
  5118 
  5189 
  5119 	if (_index <= _len2) {
  5190         if (_index <= _len2) {
  5120 	    /*
  5191             /*
  5121 	     * cannot continue with shorts - there is an odd number of
  5192              * cannot continue with shorts - there is an odd number of
  5122 	     * bytes in the minuent
  5193              * bytes in the minuent
  5123 	     */
  5194              */
  5124 	} else {
  5195         } else {
  5125 	    while (_index < _len1) {
  5196             while (_index < _len1) {
  5126 		/* 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 */
  5127 		_diff = ((unsigned short *)(_myDigits+_index-1))[0];
  5198                 _diff = ((unsigned short *)(_myDigits+_index-1))[0];
  5128 		_diff -= _borrow;
  5199                 _diff -= _borrow;
  5129 		if (_diff >= 0) {
  5200                 if (_diff >= 0) {
  5130 		    /* _borrow = 0; */
  5201                     /* _borrow = 0; */
  5131 		    ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5202                     ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5132 		    anyBitNonZero |= (_diff & 0xFFFF);
  5203                     anyBitNonZero |= (_diff & 0xFFFF);
  5133 		    _index += 2;
  5204                     _index += 2;
  5134 		    while (_index < _len1) {
  5205                     while (_index < _len1) {
  5135 			anyBitNonZero |= ((unsigned short *)(_myDigits+_index-1))[0];
  5206                         anyBitNonZero |= ((unsigned short *)(_myDigits+_index-1))[0];
  5136 			if (anyBitNonZero) {
  5207                         if (anyBitNonZero) {
  5137 			    RETURN (true);
  5208                             RETURN (true);
  5138 			}
  5209                         }
  5139 			_index += 2;
  5210                         _index += 2;
  5140 		    }
  5211                     }
  5141 		    /* last odd index */
  5212                     /* last odd index */
  5142 		    if (_index <= _len1) {
  5213                     if (_index <= _len1) {
  5143 			anyBitNonZero |= _myDigits[_index - 1];;
  5214                         anyBitNonZero |= _myDigits[_index - 1];;
  5144 			if (anyBitNonZero) {
  5215                         if (anyBitNonZero) {
  5145 			    RETURN (true);
  5216                             RETURN (true);
  5146 			}
  5217                         }
  5147 			_index++;
  5218                         _index++;
  5148 		    }
  5219                     }
  5149 		    RETURN (anyBitNonZero ? true : false);
  5220                     RETURN (anyBitNonZero ? true : false);
  5150 		}
  5221                 }
  5151 		_borrow = 1;
  5222                 _borrow = 1;
  5152 		/* _diff += 0x10000; */
  5223                 /* _diff += 0x10000; */
  5153 
  5224 
  5154 		((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5225                 ((unsigned short *)(_myDigits+_index-1))[0] = _diff;
  5155 		anyBitNonZero |= (_diff & 0xFFFF);
  5226                 anyBitNonZero |= (_diff & 0xFFFF);
  5156 		_index += 2;
  5227                 _index += 2;
  5157 	    }
  5228             }
  5158 	}
  5229         }
  5159 #endif
  5230 #endif
  5160 	/*
  5231         /*
  5161 	 * subtract byte-wise
  5232          * subtract byte-wise
  5162 	 */
  5233          */
  5163 	while (_index <= _len2) {
  5234         while (_index <= _len2) {
  5164 	    /* 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 */
  5165 	    _diff = _myDigits[_index - 1];
  5236             _diff = _myDigits[_index - 1];
  5166 	    _diff -= _otherDigits[_index - 1];
  5237             _diff -= _otherDigits[_index - 1];
  5167 	    _diff -= _borrow;
  5238             _diff -= _borrow;
  5168 	    if (_diff >= 0) {
  5239             if (_diff >= 0) {
  5169 		_borrow = 0;
  5240                 _borrow = 0;
  5170 	    } else {
  5241             } else {
  5171 		_borrow = 1;
  5242                 _borrow = 1;
  5172 		/* _diff += 0x100; */
  5243                 /* _diff += 0x100; */
  5173 	    }
  5244             }
  5174 	    _myDigits[_index - 1] = _diff;
  5245             _myDigits[_index - 1] = _diff;
  5175 	    anyBitNonZero |= (_diff & 0xFF);
  5246             anyBitNonZero |= (_diff & 0xFF);
  5176 	    _index++;
  5247             _index++;
  5177 	}
  5248         }
  5178 
  5249 
  5179 	while (_index <= _len1) {
  5250         while (_index <= _len1) {
  5180 	    /* 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 */
  5181 	    _diff = _myDigits[_index - 1];
  5252             _diff = _myDigits[_index - 1];
  5182 	    _diff -= _borrow;
  5253             _diff -= _borrow;
  5183 	    if (_diff >= 0) {
  5254             if (_diff >= 0) {
  5184 		/* _borrow = 0; */
  5255                 /* _borrow = 0; */
  5185 		_myDigits[_index - 1] = _diff;
  5256                 _myDigits[_index - 1] = _diff;
  5186 		anyBitNonZero |= (_diff & 0xFF);
  5257                 anyBitNonZero |= (_diff & 0xFF);
  5187 		_index++;
  5258                 _index++;
  5188 		while (_index <= _len1) {
  5259                 while (_index <= _len1) {
  5189 		    anyBitNonZero |= _myDigits[_index - 1];
  5260                     anyBitNonZero |= _myDigits[_index - 1];
  5190 		    if (anyBitNonZero) {
  5261                     if (anyBitNonZero) {
  5191 			RETURN (true);
  5262                         RETURN (true);
  5192 		    }
  5263                     }
  5193 		    _index++;
  5264                     _index++;
  5194 		}
  5265                 }
  5195 		break;
  5266                 break;
  5196 	    }
  5267             }
  5197 	    _borrow = 1;
  5268             _borrow = 1;
  5198 	    /* _diff += 0x100; */
  5269             /* _diff += 0x100; */
  5199 
  5270 
  5200 	    _myDigits[_index - 1] = _diff;
  5271             _myDigits[_index - 1] = _diff;
  5201 	    anyBitNonZero |= (_diff & 0xFF);
  5272             anyBitNonZero |= (_diff & 0xFF);
  5202 	    _index++;
  5273             _index++;
  5203 	}
  5274         }
  5204 	RETURN (anyBitNonZero ? true : false);
  5275         RETURN (anyBitNonZero ? true : false);
  5205     }
  5276     }
  5206 %}.
  5277 %}.
  5207 
  5278 
  5208     index := 1.
  5279     index := 1.
  5209     borrow := 0.
  5280     borrow := 0.
  5210 
  5281 
  5211     [index <= len1] whileTrue:[
  5282     [index <= len1] whileTrue:[
  5212 	diff := borrow.
  5283         diff := borrow.
  5213 	diff := diff + (digitByteArray basicAt:index).
  5284         diff := diff + (digitByteArray basicAt:index).
  5214 	index <= len2 ifTrue:[
  5285         index <= len2 ifTrue:[
  5215 	    diff := diff - (otherDigitByteArray basicAt:index).
  5286             diff := diff - (otherDigitByteArray basicAt:index).
  5216 	].
  5287         ].
  5217 
  5288 
  5218 	"/ workaround for
  5289         "/ workaround for
  5219 	"/ gcc code generator bug
  5290         "/ gcc code generator bug
  5220 
  5291 
  5221 	(diff >= 0) ifTrue:[
  5292         (diff >= 0) ifTrue:[
  5222 	    borrow := 0
  5293             borrow := 0
  5223 	] ifFalse:[
  5294         ] ifFalse:[
  5224 	    borrow := -1.
  5295             borrow := -1.
  5225 	    diff := diff + 16r100
  5296             diff := diff + 16r100
  5226 	].
  5297         ].
  5227 	diff ~~ 0 ifTrue:[
  5298         diff ~~ 0 ifTrue:[
  5228 	    notZero := true
  5299             notZero := true
  5229 	].
  5300         ].
  5230 	digitByteArray basicAt:index put:diff.
  5301         digitByteArray basicAt:index put:diff.
  5231 	index := index + 1
  5302         index := index + 1
  5232     ].
  5303     ].
  5233 
  5304 
  5234     ^ notZero
  5305     ^ notZero
  5235 
  5306 
  5236     "Created: / 5.11.1996 / 16:23:47 / cg"
  5307     "Created: / 5.11.1996 / 16:23:47 / cg"
  5247 
  5318 
  5248 %{  /* NOCONTEXT */
  5319 %{  /* NOCONTEXT */
  5249     OBJ __digits = __INST(digitByteArray);
  5320     OBJ __digits = __INST(digitByteArray);
  5250 
  5321 
  5251     if (__isByteArray(__digits)) {
  5322     if (__isByteArray(__digits)) {
  5252 	int __nBytes = __byteArraySize(__digits);
  5323         int __nBytes = __byteArraySize(__digits);
  5253 	unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
  5324         unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
  5254 	unsigned INT __this, __next;
  5325         unsigned INT __this, __next;
  5255 	int __idx;
  5326         int __idx;
  5256 
  5327 
  5257 	if (__nBytes == 1) {
  5328         if (__nBytes == 1) {
  5258 	    __bp[0] >>= 1;
  5329             __bp[0] >>= 1;
  5259 	    RETURN (self);
  5330             RETURN (self);
  5260 	}
  5331         }
  5261 
  5332 
  5262 	__idx = 1;
  5333         __idx = 1;
  5263 
  5334 
  5264 #if defined(__LSBFIRST__)
  5335 #if defined(__LSBFIRST__)
  5265 # if (__POINTER_SIZE__ == 8)
  5336 # if (__POINTER_SIZE__ == 8)
  5266 	if (sizeof(unsigned INT) == 8) {
  5337         if (sizeof(unsigned INT) == 8) {
  5267 	    int __endIndex = __nBytes - 8;
  5338             int __endIndex = __nBytes - 8;
  5268 
  5339 
  5269 	    if (__idx < __endIndex) {
  5340             if (__idx < __endIndex) {
  5270 		__this = ((unsigned INT *)__bp)[0];
  5341                 __this = ((unsigned INT *)__bp)[0];
  5271 
  5342 
  5272 		while (__idx < __endIndex) {
  5343                 while (__idx < __endIndex) {
  5273 		    __next = ((unsigned INT *)__bp)[1];
  5344                     __next = ((unsigned INT *)__bp)[1];
  5274 		    __this = (__this >> 1) /* & 0x7FFFFFFFFFFFFFF */;
  5345                     __this = (__this >> 1) /* & 0x7FFFFFFFFFFFFFF */;
  5275 		    __this |= __next << 63;
  5346                     __this |= __next << 63;
  5276 		    ((unsigned INT *)__bp)[0] = __this;
  5347                     ((unsigned INT *)__bp)[0] = __this;
  5277 		    __this = __next;
  5348                     __this = __next;
  5278 		    __bp += 8;
  5349                     __bp += 8;
  5279 		    __idx += 8;
  5350                     __idx += 8;
  5280 		}
  5351                 }
  5281 	    }
  5352             }
  5282 
  5353 
  5283 	    if (__idx < (__nBytes - 4)) {
  5354             if (__idx < (__nBytes - 4)) {
  5284 		__this = ((unsigned int *)__bp)[0];
  5355                 __this = ((unsigned int *)__bp)[0];
  5285 
  5356 
  5286 		__next = ((unsigned int *)__bp)[1];
  5357                 __next = ((unsigned int *)__bp)[1];
  5287 		__this = (__this >> 1) /* & 0x7FFFFFF */;
  5358                 __this = (__this >> 1) /* & 0x7FFFFFF */;
  5288 		__this |= __next << 31;
  5359                 __this |= __next << 31;
  5289 		((unsigned int *)__bp)[0] = __this;
  5360                 ((unsigned int *)__bp)[0] = __this;
  5290 		__this = __next;
  5361                 __this = __next;
  5291 		__bp += 4;
  5362                 __bp += 4;
  5292 		__idx += 4;
  5363                 __idx += 4;
  5293 	    }
  5364             }
  5294 	    if (__idx < (__nBytes - 2)) {
  5365             if (__idx < (__nBytes - 2)) {
  5295 		__this = ((unsigned short *)__bp)[0];
  5366                 __this = ((unsigned short *)__bp)[0];
  5296 
  5367 
  5297 		__next = ((unsigned short *)__bp)[1];
  5368                 __next = ((unsigned short *)__bp)[1];
  5298 		__this = (__this >> 1) /* & 0x7FFFFFF */;
  5369                 __this = (__this >> 1) /* & 0x7FFFFFF */;
  5299 		__this |= __next << 15;
  5370                 __this |= __next << 15;
  5300 		((unsigned short *)__bp)[0] = __this;
  5371                 ((unsigned short *)__bp)[0] = __this;
  5301 		__this = __next;
  5372                 __this = __next;
  5302 		__bp += 2;
  5373                 __bp += 2;
  5303 		__idx += 2;
  5374                 __idx += 2;
  5304 	    }
  5375             }
  5305 	}
  5376         }
  5306 # else
  5377 # else
  5307 	if (sizeof(unsigned int) == 4) {
  5378         if (sizeof(unsigned int) == 4) {
  5308 	    int __endIndex = __nBytes - 4;
  5379             int __endIndex = __nBytes - 4;
  5309 
  5380 
  5310 	    if (__idx < __endIndex) {
  5381             if (__idx < __endIndex) {
  5311 		__this = ((unsigned int *)__bp)[0];
  5382                 __this = ((unsigned int *)__bp)[0];
  5312 
  5383 
  5313 		while (__idx < __endIndex) {
  5384                 while (__idx < __endIndex) {
  5314 		    __next = ((unsigned int *)__bp)[1];
  5385                     __next = ((unsigned int *)__bp)[1];
  5315 		    __this = (__this >> 1) /* & 0x7FFFFFF */;
  5386                     __this = (__this >> 1) /* & 0x7FFFFFF */;
  5316 		    __this |= __next << 31;
  5387                     __this |= __next << 31;
  5317 		    ((unsigned int *)__bp)[0] = __this;
  5388                     ((unsigned int *)__bp)[0] = __this;
  5318 		    __this = __next;
  5389                     __this = __next;
  5319 		    __bp += 4;
  5390                     __bp += 4;
  5320 		    __idx += 4;
  5391                     __idx += 4;
  5321 		}
  5392                 }
  5322 	    }
  5393             }
  5323 	}
  5394         }
  5324 # endif
  5395 # endif
  5325 #endif
  5396 #endif
  5326 
  5397 
  5327 	__this = __bp[0];
  5398         __this = __bp[0];
  5328 	while (__idx < __nBytes) {
  5399         while (__idx < __nBytes) {
  5329 	    __next = __bp[1];
  5400             __next = __bp[1];
  5330 	    __this >>= 1;
  5401             __this >>= 1;
  5331 	    __this |= __next << 7;
  5402             __this |= __next << 7;
  5332 	    __bp[0] = __this;
  5403             __bp[0] = __this;
  5333 	    __this = __next;
  5404             __this = __next;
  5334 	    __bp++;
  5405             __bp++;
  5335 	    __idx++;
  5406             __idx++;
  5336 	}
  5407         }
  5337 	__bp[0] = __this >> 1;
  5408         __bp[0] = __this >> 1;
  5338 	RETURN (self);
  5409         RETURN (self);
  5339     }
  5410     }
  5340 %}.
  5411 %}.
  5341 
  5412 
  5342     prevBit := 0.
  5413     prevBit := 0.
  5343     digitByteArray size to:1 by:-1 do:[:idx |
  5414     digitByteArray size to:1 by:-1 do:[:idx |
  5344 	|thisByte|
  5415         |thisByte|
  5345 
  5416 
  5346 	thisByte := digitByteArray at:idx.
  5417         thisByte := digitByteArray at:idx.
  5347 	digitByteArray at:idx put:((thisByte bitShift:-1) bitOr:prevBit).
  5418         digitByteArray at:idx put:((thisByte bitShift:-1) bitOr:prevBit).
  5348 	prevBit := (thisByte bitAnd:1) bitShift:7.
  5419         prevBit := (thisByte bitAnd:1) bitShift:7.
  5349     ].
  5420     ].
  5350 
  5421 
  5351     "
  5422     "
  5352      100000 asLargeInteger div2
  5423      100000 asLargeInteger div2
  5353      1000000000000000000000000000 div2
  5424      1000000000000000000000000000 div2
  5367 
  5438 
  5368     nBytes := digitByteArray size.
  5439     nBytes := digitByteArray size.
  5369 
  5440 
  5370     b := digitByteArray at:nBytes.
  5441     b := digitByteArray at:nBytes.
  5371     (b bitAnd:16r80) ~~ 0 ifTrue:[
  5442     (b bitAnd:16r80) ~~ 0 ifTrue:[
  5372 	"/ need another byte
  5443         "/ need another byte
  5373 	nBytes := nBytes + 1.
  5444         nBytes := nBytes + 1.
  5374 	t := ByteArray uninitializedNew:nBytes.
  5445         t := ByteArray uninitializedNew:nBytes.
  5375 	t replaceFrom:1 to:nBytes-1 with:digitByteArray startingAt:1.
  5446         t replaceFrom:1 to:nBytes-1 with:digitByteArray startingAt:1.
  5376 	t at:nBytes put:0.
  5447         t at:nBytes put:0.
  5377 	digitByteArray := t.
  5448         digitByteArray := t.
  5378     ].
  5449     ].
  5379 
  5450 
  5380 %{
  5451 %{
  5381     OBJ __digits = __INST(digitByteArray);
  5452     OBJ __digits = __INST(digitByteArray);
  5382 
  5453 
  5383     if (__isByteArray(__digits)) {
  5454     if (__isByteArray(__digits)) {
  5384 	int __nBytes = __intVal(nBytes);
  5455         int __nBytes = __intVal(nBytes);
  5385 	unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
  5456         unsigned char *__bp = __ByteArrayInstPtr(__digits)->ba_element;
  5386 	unsigned INT __carry = 0, __newCarry;
  5457         unsigned INT __carry = 0, __newCarry;
  5387 
  5458 
  5388 #if defined(__LSBFIRST__)
  5459 #if defined(__LSBFIRST__)
  5389 # if (__POINTER_SIZE__ == 8)
  5460 # if (__POINTER_SIZE__ == 8)
  5390 	if (sizeof(unsigned INT) == 8) {
  5461         if (sizeof(unsigned INT) == 8) {
  5391 	    while (__nBytes >= 8) {
  5462             while (__nBytes >= 8) {
  5392 		unsigned INT __this;
  5463                 unsigned INT __this;
  5393 
  5464 
  5394 		__this = ((unsigned INT *)__bp)[0];
  5465                 __this = ((unsigned INT *)__bp)[0];
  5395 		__newCarry = (__this >> 63) /* & 1 */;
  5466                 __newCarry = (__this >> 63) /* & 1 */;
  5396 		((unsigned INT *)__bp)[0] = (__this << 1) | __carry;
  5467                 ((unsigned INT *)__bp)[0] = (__this << 1) | __carry;
  5397 		__carry = __newCarry;
  5468                 __carry = __newCarry;
  5398 		__bp += 8;
  5469                 __bp += 8;
  5399 		__nBytes -= 8;
  5470                 __nBytes -= 8;
  5400 	    }
  5471             }
  5401 	}
  5472         }
  5402 # endif
  5473 # endif
  5403 	if (sizeof(unsigned int) == 4) {
  5474         if (sizeof(unsigned int) == 4) {
  5404 	    while (__nBytes >= 4) {
  5475             while (__nBytes >= 4) {
  5405 		unsigned int __this;
  5476                 unsigned int __this;
  5406 
  5477 
  5407 		__this = ((unsigned int *)__bp)[0];
  5478                 __this = ((unsigned int *)__bp)[0];
  5408 		__newCarry = (__this >> 31) /* & 1 */;
  5479                 __newCarry = (__this >> 31) /* & 1 */;
  5409 		((unsigned int *)__bp)[0] = (__this << 1) | __carry;
  5480                 ((unsigned int *)__bp)[0] = (__this << 1) | __carry;
  5410 		__carry = __newCarry;
  5481                 __carry = __newCarry;
  5411 		__bp += 4;
  5482                 __bp += 4;
  5412 		__nBytes -= 4;
  5483                 __nBytes -= 4;
  5413 	    }
  5484             }
  5414 	}
  5485         }
  5415 	if (__nBytes >= 2) {
  5486         if (__nBytes >= 2) {
  5416 	    unsigned short __this;
  5487             unsigned short __this;
  5417 
  5488 
  5418 	    __this = ((unsigned short *)__bp)[0];
  5489             __this = ((unsigned short *)__bp)[0];
  5419 	    __newCarry = (__this >> 15) /* & 1 */;
  5490             __newCarry = (__this >> 15) /* & 1 */;
  5420 	    ((unsigned short *)__bp)[0] = (__this << 1) | __carry;
  5491             ((unsigned short *)__bp)[0] = (__this << 1) | __carry;
  5421 	    __carry = __newCarry;
  5492             __carry = __newCarry;
  5422 	    __bp += 2;
  5493             __bp += 2;
  5423 	    __nBytes -= 2;
  5494             __nBytes -= 2;
  5424 	}
  5495         }
  5425 #endif /* LSBFIRST */
  5496 #endif /* LSBFIRST */
  5426 	while (__nBytes) {
  5497         while (__nBytes) {
  5427 	    unsigned char __this;
  5498             unsigned char __this;
  5428 
  5499 
  5429 	    __this = __bp[0];
  5500             __this = __bp[0];
  5430 	    __newCarry = (__this >> 7) /* & 1 */;
  5501             __newCarry = (__this >> 7) /* & 1 */;
  5431 	    __bp[0] = (__this << 1) | __carry;
  5502             __bp[0] = (__this << 1) | __carry;
  5432 	    __carry = __newCarry;
  5503             __carry = __newCarry;
  5433 	    __bp++;
  5504             __bp++;
  5434 	    __nBytes--;
  5505             __nBytes--;
  5435 	}
  5506         }
  5436 	RETURN (self);
  5507         RETURN (self);
  5437     }
  5508     }
  5438 %}.
  5509 %}.
  5439 
  5510 
  5440     prevBit := 0.
  5511     prevBit := 0.
  5441     1 to:digitByteArray size do:[:idx |
  5512     1 to:digitByteArray size do:[:idx |
  5442 	|thisByte|
  5513         |thisByte|
  5443 
  5514 
  5444 	thisByte := digitByteArray at:idx.
  5515         thisByte := digitByteArray at:idx.
  5445 	digitByteArray at:idx put:(((thisByte bitShift:1) bitAnd:16rFF) bitOr:prevBit).
  5516         digitByteArray at:idx put:(((thisByte bitShift:1) bitAnd:16rFF) bitOr:prevBit).
  5446 	prevBit := (thisByte bitShift:-7) bitAnd:1.
  5517         prevBit := (thisByte bitShift:-7) bitAnd:1.
  5447     ].
  5518     ].
  5448 
  5519 
  5449     "
  5520     "
  5450      100000 asLargeInteger mul2
  5521      100000 asLargeInteger mul2
  5451      16r7FFFFFFFFFFF copy mul2 hexPrintString
  5522      16r7FFFFFFFFFFF copy mul2 hexPrintString