Integer.st
changeset 1 a27a279701f8
child 3 24d81bf47225
equal deleted inserted replaced
0:aa2498ef6470 1:a27a279701f8
       
     1 "
       
     2  COPYRIGHT (c) 1988-93 by Claus Gittinger
       
     3               All Rights Reserved
       
     4 
       
     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
       
     7  inclusion of the above copyright notice.   This software may not
       
     8  be provided or otherwise made available to, or used by, any
       
     9  other person.  No title to or ownership of the software is
       
    10  hereby transferred.
       
    11 "
       
    12 
       
    13 Number subclass:#Integer
       
    14        instanceVariableNames:''
       
    15        classVariableNames:''
       
    16        poolDictionaries:''
       
    17        category:'Magnitude-Numbers'
       
    18 !
       
    19 
       
    20 Integer comment:'
       
    21 
       
    22 COPYRIGHT (c) 1988-93 by Claus Gittinger
       
    23               All Rights Reserved
       
    24 
       
    25 abstract superclass for all integer numbers
       
    26 
       
    27 %W% %E%
       
    28 written 88 by claus
       
    29 '!
       
    30 
       
    31 !Integer class methodsFor:'constants'!
       
    32 
       
    33 zero
       
    34     ^ 0
       
    35 !
       
    36 
       
    37 unity
       
    38     ^ 1
       
    39 ! !
       
    40 
       
    41 !Integer methodsFor:'arithmetic'!
       
    42 
       
    43 quo:aNumber
       
    44     "Return the integer quotient of dividing the receiver by aNumber with
       
    45     truncation towards zero. For Integers this is same as //"
       
    46 
       
    47     ^ self // aNumber
       
    48 
       
    49 ! !
       
    50 
       
    51 !Integer methodsFor:'double dispatching'!
       
    52 
       
    53 sumFromFraction:aFraction
       
    54     "sent when a fraction does not know how to add the recevier, an integer"
       
    55 
       
    56     ^ (Fraction numerator:(aFraction numerator
       
    57                            + (self * aFraction denominator))
       
    58               denominator:aFraction denominator) reduced
       
    59 !
       
    60 
       
    61 differenceFromFraction:aFraction
       
    62     "sent when a fraction does not know how to subtract the recevier, an integer"
       
    63 
       
    64     ^ (Fraction numerator:((self * aFraction denominator) - aFraction numerator)
       
    65               denominator:aFraction denominator) reduced
       
    66 !
       
    67 
       
    68 productFromFraction:aFraction
       
    69     "sent when a fraction does not know how to multiply the recevier, an integer"
       
    70 
       
    71     ^ (Fraction numerator:(self * aFraction numerator)
       
    72               denominator:aFraction denominator) reduced
       
    73 ! !
       
    74 
       
    75 !Integer methodsFor:'truncation & rounding'!
       
    76 
       
    77 ceiling
       
    78     "I am my ceiling"
       
    79 
       
    80     ^ self
       
    81 !
       
    82 
       
    83 floor
       
    84     "I am my floor"
       
    85 
       
    86     ^ self
       
    87 !
       
    88 
       
    89 rounded
       
    90     "return the receiver rounded toward the next Integer -
       
    91      for integers this is self"
       
    92 
       
    93     ^ self
       
    94 !
       
    95 
       
    96 truncated
       
    97     "return the receiver truncated towards zero - 
       
    98      for integers this is self"
       
    99 
       
   100     ^ self
       
   101 ! !
       
   102 
       
   103 !Integer methodsFor:'queries'!
       
   104 
       
   105 digitLength
       
   106     "return the number of bytes needed for the binary representation
       
   107      of the receiver"
       
   108 
       
   109     ^ (self log:256) ceiling asInteger
       
   110 !
       
   111 
       
   112 digitAt:n
       
   113     "return the n-th byte of the binary representation"
       
   114 
       
   115     |num count|
       
   116 
       
   117     num := self.
       
   118     count := n.
       
   119     [count > 1] whileTrue:[
       
   120         num := num // 256.
       
   121         count := count - 1
       
   122     ].
       
   123     ^ num \\ 256
       
   124 !
       
   125 
       
   126 isInteger
       
   127     "return true, if the receiver is some kind of integer number"
       
   128 
       
   129     ^ true
       
   130 ! !
       
   131 
       
   132 !Integer methodsFor:'misc math'!
       
   133 
       
   134 factorial
       
   135     "return 1*2*3...*self"
       
   136 
       
   137     (self > 1) ifTrue:[
       
   138         ^ self * (self - 1) factorial
       
   139     ].
       
   140     ^ self
       
   141 !
       
   142 
       
   143 gcd:anInteger
       
   144     "return the greatest common divisor (Euclid's algorithm)"
       
   145 
       
   146     |ttt selfInteger temp|
       
   147 
       
   148     ttt := anInteger.
       
   149     selfInteger := self.
       
   150     [ttt ~~ 0] whileTrue:[
       
   151         temp := selfInteger \\ ttt.
       
   152         selfInteger := ttt.
       
   153         ttt := temp
       
   154     ].
       
   155     ^ selfInteger
       
   156 !
       
   157 
       
   158 lcm:anInteger
       
   159     ^(self * anInteger) abs // (self gcd: anInteger)
       
   160 !
       
   161 
       
   162 fib
       
   163     "dont use this method if you need fibionacci numbers -
       
   164      this method is for benchmarking purposes only.
       
   165      (use fastFib instead and dont ever try 60 fib ...)"
       
   166 
       
   167     (self > 1) ifTrue:[
       
   168         ^ (self - 1) fib + (self - 2) fib
       
   169     ].
       
   170     ^ 1
       
   171 
       
   172     "Time millisecondsToRun:[30 fib]"
       
   173 !
       
   174 
       
   175 fastFib
       
   176     "this method just to show how a changed algorithm can
       
   177      change things much more drastic than tuning ...
       
   178      (compare 30 fib with 30 fastFib / dont even try 60 fib)"
       
   179 
       
   180     |fib|
       
   181 
       
   182     self <= 1 ifTrue:[^ 1].
       
   183 
       
   184     FibCache isNil ifTrue:[
       
   185         FibCache := OrderedCollection new
       
   186     ].
       
   187     FibCache size >= self ifTrue:[
       
   188         ^ FibCache at:self
       
   189     ].
       
   190     fib := (self - 2) fastFib + (self - 1) fastFib.
       
   191 
       
   192     FibCache grow:self.
       
   193     FibCache at:self put:fib.
       
   194     ^ fib
       
   195 
       
   196     "Time millisecondsToRun:[30 fastFib]"
       
   197 !
       
   198 
       
   199 acker:n
       
   200     "return the value of acker(self, n)"
       
   201 
       
   202     (self == 0) ifTrue:[^ n + 1].
       
   203     (n == 0) ifTrue:[^ (self - 1) acker: 1].
       
   204     ^ (self - 1) acker:(self acker:(n - 1))
       
   205 
       
   206     "3 acker:2"
       
   207 ! !
       
   208 
       
   209 !Integer methodsFor:'coercing and converting'!
       
   210 
       
   211 asFraction
       
   212     "return a Fraction with same value as receiver"
       
   213 
       
   214     ^ Fraction numerator:self denominator:1
       
   215 !
       
   216 
       
   217 asInteger
       
   218     "return the receiver truncated towards zero - 
       
   219      for integers this is self"
       
   220 
       
   221     ^ self
       
   222 ! !
       
   223 
       
   224 !Integer methodsFor:'printing & storing'!
       
   225 
       
   226 storeString
       
   227     "return a string for storing - printString will do"
       
   228 
       
   229     ^ self printString
       
   230 !
       
   231 
       
   232 printString
       
   233     "return a string representation of the receiver"
       
   234 
       
   235     ^ self printStringRadix:10
       
   236 !
       
   237 
       
   238 radixPrintStringRadix:aRadix
       
   239     "return a string representation of the receiver in the specified
       
   240      radix; prepend XXr to the string"
       
   241 
       
   242     ^ (aRadix printString) , 'r', (self printStringRadix:aRadix)
       
   243 
       
   244     "31 radixPrintStringRadix:2 "
       
   245     "31 radixPrintStringRadix:3 "
       
   246     "31 radixPrintStringRadix:36 "
       
   247 !
       
   248 
       
   249 printStringRadix:aRadix
       
   250     "return a string representation of the receiver in the specified
       
   251      radix (without the initial XXr)"
       
   252 
       
   253     |leftPart|
       
   254 
       
   255     (self = 0) ifTrue:[^ '0'].
       
   256     (self < 0) ifTrue:[
       
   257         ^ '-' , (self negated printStringRadix:aRadix)
       
   258     ].
       
   259     leftPart := self // aRadix.
       
   260     (leftPart ~= 0) ifTrue:[
       
   261         ^ (leftPart printStringRadix:aRadix) copyWith:(Character digitValue:(self \\ aRadix))
       
   262     ].
       
   263     ^ (Character digitValue:self) asString
       
   264 !
       
   265 
       
   266 printStringRadix:aRadix size:sz fill:fillCharacter
       
   267     "return a string representation of the receiver in the specified
       
   268      radix. The string is padded on the left with fillCharacter to make
       
   269      its size as specified in sz."
       
   270 
       
   271      |s|
       
   272 
       
   273     s := self printStringRadix:aRadix.
       
   274     s size < sz ifTrue:[
       
   275         s := ((String new:(sz - s size)) atAllPut:fillCharacter) , s
       
   276     ].
       
   277     ^ s
       
   278 
       
   279     "1024 printStringRadix:16 size:4 fill:$0"
       
   280 ! !
       
   281 
       
   282 !Integer class methodsFor:'instance creation'!
       
   283 
       
   284 readFrom:aStream radix:radix
       
   285     "return the next Integer from the (character-)stream aStream in radix;
       
   286      (assumes that the initial XXR has already been read)
       
   287      no whitespace-skipping; returns 0 if no number available"
       
   288 
       
   289     |nextChar value|
       
   290 
       
   291     nextChar := aStream peek.
       
   292     value := 0.
       
   293     [nextChar notNil and:[nextChar isDigitRadix:radix]] whileTrue:[
       
   294         value := value * radix + nextChar digitValue.
       
   295         nextChar := aStream nextPeek
       
   296     ].
       
   297     ^ value
       
   298 !
       
   299 
       
   300 readFrom:aStream
       
   301     "return the next Integer from the (character-)stream aStream,
       
   302      handling initial XXr for arbitrary radix numbers and initial
       
   303      sign.
       
   304      skipping all whitespace first; return nil if no number"
       
   305 
       
   306     |nextChar value negative|
       
   307 
       
   308     nextChar := aStream skipSeparators.
       
   309     (nextChar == $-) ifTrue:[
       
   310         negative := true.
       
   311         nextChar := aStream nextPeek
       
   312     ] ifFalse:[
       
   313         negative := false
       
   314     ].
       
   315     nextChar isDigit ifFalse:[ ^ nil].
       
   316     value := Integer readFrom:aStream radix:10.
       
   317     nextChar := aStream peek.
       
   318     ((nextChar == $r) or:[ nextChar == $R]) ifTrue:[
       
   319         aStream next.
       
   320         value := Integer readFrom:aStream radix:value
       
   321     ].
       
   322     negative ifTrue:[
       
   323         ^ value negated
       
   324     ].
       
   325     ^ value
       
   326 ! !
       
   327 
       
   328 !Integer methodsFor:'benchmarking'!
       
   329 
       
   330 sieve
       
   331     "sieve the primes self times"
       
   332 
       
   333     |num i k prime count flags time|
       
   334 
       
   335     num := 8191.
       
   336     flags := Array new:num.
       
   337 
       
   338     Transcript show:'Sieve running ...'.
       
   339     Transcript cr.
       
   340 
       
   341     time := Time millisecondsToRun:[
       
   342         self timesRepeat:[
       
   343             count := 0.
       
   344             flags atAllPut:1.
       
   345             i := 1.
       
   346             num timesRepeat:[
       
   347                 (flags at:i) == 1 ifTrue:[
       
   348                     prime := i + i + 3.
       
   349                     k := i + prime.
       
   350                     [k <= num] whileTrue:[
       
   351                         flags at:k put:0.
       
   352                         k := k + prime
       
   353                     ].
       
   354                     count := count + 1
       
   355                 ].
       
   356                 i := i + 1
       
   357             ].
       
   358         ].
       
   359     ].
       
   360     Transcript show:'Sieve in Smalltalk: '.
       
   361     Transcript show:self printString. 
       
   362     Transcript showCr:' iteration(s).'.
       
   363     Transcript show:'found '. 
       
   364     Transcript show:count printString. 
       
   365     Transcript showCr:' primes.' .
       
   366     Transcript show:'time per run: '. 
       
   367     Transcript show:(time / self) printString. 
       
   368     Transcript showCr:' ms.'
       
   369 
       
   370     "1 sieve"
       
   371 !
       
   372 
       
   373 sieveWithIntegers
       
   374     "sieve the primes self times"
       
   375 
       
   376     |num        "<SmallInteger>"
       
   377      i          "<SmallInteger>"
       
   378      k          "<SmallInteger>"
       
   379      prime      "<SmallInteger>"
       
   380      count      "<SmallInteger>"
       
   381      flags time|
       
   382 
       
   383     num := 8191.
       
   384     flags := Array new:num.
       
   385 
       
   386     Transcript show:'Sieve running ...'.
       
   387     Transcript cr.
       
   388 
       
   389     time := Time millisecondsToRun:[
       
   390         self timesRepeat:[
       
   391             count := 0.
       
   392             flags atAllPut:1.
       
   393             i := 1.
       
   394             num timesRepeat:[
       
   395                 (flags at:i) == 1 ifTrue:[
       
   396                     prime := i + i + 3.
       
   397                     k := i + prime.
       
   398                     [k <= num] whileTrue:[
       
   399                         flags at:k put:0.
       
   400                         k := k + prime
       
   401                     ].
       
   402                     count := count + 1
       
   403                 ].
       
   404                 i := i + 1
       
   405             ].
       
   406         ].
       
   407     ].
       
   408     Transcript show:'Sieve in Smalltalk: '.
       
   409     Transcript show:self printString. 
       
   410     Transcript showCr:' iteration(s).'.
       
   411     Transcript show:'found '. 
       
   412     Transcript show:count printString. 
       
   413     Transcript showCr:' primes.' .
       
   414     Transcript show:'time per run: '. 
       
   415     Transcript show:(time / self) printString. 
       
   416     Transcript showCr:' ms.'
       
   417 
       
   418     "1 sieveWithIntegers"
       
   419 !
       
   420 
       
   421 recur1:num
       
   422     "actual recursion method for recur1"
       
   423 
       
   424     (num = 0) ifTrue:[^ self].
       
   425     self recur1:(num - 1).
       
   426     ^ self recur1:(num - 1)
       
   427 !
       
   428 
       
   429 recur1
       
   430     "lots of recursion for testing send with arg"
       
   431 
       
   432     |t|
       
   433 
       
   434     t := Time millisecondsToRun:[
       
   435         1 recur1:15
       
   436     ].
       
   437     Transcript showCr:(t printString)
       
   438 
       
   439     "1 recur1"
       
   440 !
       
   441 
       
   442 recur2
       
   443     "lots of recursion for testing send without arg"
       
   444 
       
   445     (self > 0) ifTrue:[
       
   446         (self - 1) recur2.
       
   447         ^ (self - 1) recur2
       
   448     ]
       
   449 
       
   450     "Transcript showCr:(
       
   451         Time millisecondsToRun:[
       
   452             15 recur2
       
   453         ]
       
   454      ) printString"
       
   455 !
       
   456 
       
   457 countDown
       
   458     |t index|
       
   459 
       
   460     t := Time millisecondsToRun:[
       
   461         index := 100000.
       
   462         [index > 0] whileTrue:[
       
   463             index := index - 1
       
   464         ].
       
   465     ].
       
   466     Transcript showCr:(t printString)
       
   467 
       
   468     "1 countDown"
       
   469 !
       
   470 
       
   471 countDown2
       
   472     |t|
       
   473 
       
   474     t := Time millisecondsToRun:[
       
   475         |index|
       
   476 
       
   477         index := 100000.
       
   478         [index > 0] whileTrue:[
       
   479             index := index - 1
       
   480         ].
       
   481     ].
       
   482     Transcript showCr:(t printString)
       
   483 
       
   484     "1 countDown2"
       
   485 !
       
   486 
       
   487 noop
       
   488     ^ self
       
   489 !
       
   490 
       
   491 send:num
       
   492     "lots of message sends"
       
   493 
       
   494     |t|
       
   495 
       
   496     t := Time millisecondsToRun:[
       
   497         num timesRepeat:[
       
   498             self noop
       
   499         ].
       
   500     ].
       
   501     Transcript showCr:(t printString)
       
   502 
       
   503     "1 send:100000"
       
   504 !
       
   505 
       
   506 memory
       
   507     "lots of memory allocation"
       
   508 
       
   509     |t|
       
   510 
       
   511     t := Time millisecondsToRun:[
       
   512         self timesRepeat:[
       
   513             Array new:500
       
   514         ].
       
   515     ].
       
   516     Transcript showCr:(t printString)
       
   517 
       
   518     "10000 memory"
       
   519 !
       
   520 
       
   521 benchArithmetic
       
   522     "arithmetic speed bench"
       
   523 
       
   524     |p n m t|
       
   525 
       
   526     n := 3.0.
       
   527     m := 5.5.
       
   528 
       
   529     t := Time millisecondsToRun:[
       
   530         self timesRepeat:[
       
   531             p := 5 / n + m
       
   532         ]
       
   533     ].
       
   534     Transcript showCr:(t printString)
       
   535 
       
   536     "10000 benchArithmetic"
       
   537 !
       
   538 
       
   539 sumTo
       
   540     |val|
       
   541 
       
   542     100 timesRepeat:[
       
   543         val := 0.
       
   544         1 to:10000 do:[:i |
       
   545             val := val + i
       
   546         ]
       
   547     ].
       
   548     "Time millisecondsToRun:[1 sumTo]"
       
   549 !
       
   550 
       
   551 fastSumTo
       
   552     |val i|
       
   553 
       
   554     100 timesRepeat:[
       
   555         val := 0.
       
   556         i := 1.
       
   557         [i <= 10000] whileTrue:[
       
   558             val := val + i.
       
   559             i := i + 1
       
   560         ].
       
   561     ].
       
   562     "Time millisecondsToRun:[1 fastSumTo]"
       
   563 !
       
   564 
       
   565 nestedLoop
       
   566     |i|
       
   567 
       
   568     100 timesRepeat:[
       
   569         i := 0.
       
   570         1 to:100 do:[:l1 |
       
   571             1 to:100 do:[:l2 |
       
   572                 i := i + 1
       
   573             ]
       
   574         ]
       
   575     ]
       
   576     "Time millisecondsToRun:[1 nestedLoop]"
       
   577 !
       
   578 
       
   579 atAllPut
       
   580     |vec t|
       
   581 
       
   582     vec := Array new:100000.
       
   583     t := Time millisecondsToRun:[
       
   584         1 to:100000 do:[:i |
       
   585             vec at:i put:7
       
   586         ]
       
   587     ].
       
   588     ^ t
       
   589 
       
   590     "1  atAllPut"
       
   591 !
       
   592 
       
   593 atAllPut2
       
   594     |array t|
       
   595 
       
   596     array := Array new:100000.
       
   597     t := Time millisecondsToRun:[
       
   598         1 to:100000 do:[:i |
       
   599             array at:i put:7
       
   600         ]
       
   601     ].
       
   602     ^ t
       
   603 
       
   604     "1  atAllPut2"
       
   605 !
       
   606 
       
   607 sumAll 
       
   608     |vec t s|
       
   609 
       
   610     vec := Array new:100000.
       
   611     1 to:100000 do:[:i |
       
   612         vec at:i put:7
       
   613     ].
       
   614     s := 0.
       
   615     t := Time millisecondsToRun:[
       
   616         1 to:100000 do:[:i |
       
   617             s := s + (vec at:i)
       
   618         ]
       
   619     ].
       
   620     ^ t
       
   621 
       
   622     "1  sumAll"
       
   623 !
       
   624 
       
   625 sumAll2 
       
   626     |array t s|
       
   627 
       
   628     array := Array new:100000.
       
   629     1 to:100000 do:[:i |
       
   630         array at:i put:7
       
   631     ].
       
   632     s := 0.
       
   633     t := Time millisecondsToRun:[
       
   634         1 to:100000 do:[:i |
       
   635             s := s + (array at:i)
       
   636         ]
       
   637     ].
       
   638     ^ t
       
   639 
       
   640     "1  sumAll2"
       
   641 ! !