1!Integer methodsFor: 'benchmarks'!
2
3tinyBenchmarks
4    "Report the results of running the two tiny Squeak benchmarks.
5
6     The following table lists results for various Smalltalks on a
7     300 MHz PentiumII PC.  Take these results with a grain of salt
8     and read these notes:
9
10     Notes:
11     a) An object table does hinder performance of course, but not
12     that much.  VisualWorks is still 25% faster than IBM Smalltalk,
13     and even 40% in the `send message' benchmark where the object
14     table should penalize it more.
15     b) Smalltalk MT's sending performance is poor because numbers
16     were obtained evaluating the benchmarks from the Transcript,
17     which activates a non-optimized build -- creating an indipendent
18     executable would bring numbers considerably higher.  Not owning
19     a copy Smalltalk MT I cannot do that and correct the figures.
20     c) I feel that the JIT compiler's performance is encouraging,
21     although the current architecture cannot show great improvements
22     in the sends benchmark.  Adding type inferencing will probably
23     shorten the gap with VisualWorks, which is a derivative of the
24     original ParcPlace translator!
25     d) I know that some values are for obsolete versions of the
26     tools.  Send updated values if you care.
27
28	 ,--- (B)ytecode interpreter, (J)IT compiler, static (C)ompiler
29	/ ,-- Uses (D)irect or (I)ndirect pointers
30       / /
31     ././.---------------------.---------------------.-----------------.
32     |B|I| Dolphin Smalltalk   | 17.4 Mbytecodes/sec | 1112 Ksends/sec |
33     |B|I| GST (with GCC 3.0)  | 22.4 Mbytecodes/sec | 1080 Ksends/sec |
34     |J|D| IBM Smalltalk 3.0   | 61.9 Mbytecodes/sec | 4224 Ksends/sec |
35     |J|I| GST (with JIT)      | 72.0 Mbytecodes/sec | 2625 Ksends/sec |
36     |J|I| VisualWorks 5i      | 81.8 Mbytecodes/sec | 5950 Ksends/sec |
37     |C|?| Smalltalk MT        |  128 Mbytecodes/sec | 1076 Ksends/sec |
38     '-'-----------------------'---------------------'-----------------"
39
40
41    | t1 t2 r n1 n2 |
42    n1 _ 1 bitShift: self.
43    [ObjectMemory compact. t1 _ Time millisecondsToRun: [n1 benchmark].
44     t1 < 5000] whileTrue:[ n1 _ n1 * 2 ].
45
46    n2 _ 24 + self.
47    [ObjectMemory compact. t2 _ Time millisecondsToRun: [r _ n2 benchFib].
48     t2 < 5000] whileTrue:[ n2 _ n2 + 1 ].
49
50    ^((n1 * 500000 * 1000) // t1) printString, ' bytecodes/sec; ',
51     ((r * 1000) // t2) printString, ' sends/sec'!
52
53benchFib
54    "Handy send-heavy benchmark -- result is number of sends:
55     (result // seconds to run) = approx calls per second"
56    ^self < 2
57	ifTrue: [1]
58	ifFalse: [(self - 1) benchFib + (self - 2) benchFib + 1]
59!
60
61benchmark
62    "Handy bytecode-heavy benchmark -- approx 500000 bytecodes per run:
63     (500000 * times ran // secs to run) = approx bytecodes per second"
64
65    | size flags prime k count |
66    size _ 8190.
67    flags _ Array new: size.
68    self timesRepeat: [
69	count _ 0.
70	flags atAllPut: true.
71	1 to: size do:
72	    [:i | (flags at: i) ifTrue:
73		[prime _ i+1.
74		k _ i + prime.
75		[k <= size] whileTrue:
76		    [flags at: k put: false.
77		    k _ k + prime].
78		count _ count + 1]]].
79    ^count
80! !
81
82Transcript showCr: 12 tinyBenchmarks!
83