Previous: , Up: Behind the scenes  


6.12.4 The truth of Smalltalk performance

Everybody says Smalltalk is slow, yet this is not completely true for at least three reasons. First, most of the time in graphical applications is spent waiting for the user to “do something”, and most of the time in scripting applications (which GNU Smalltalk is particularly well versed in) is spent in disk I/O; implementing a travelling salesman problem in Smalltalk would indeed be slow, but for most real applications you can indeed exchange performance for Smalltalk’s power and development speed.

Second, Smalltalk’s automatic memory management is faster than C’s manual one. Most C programs are sped up if you relink them with one of the garbage collecting systems available for C or C++.

Third, even though very few Smalltalk virtual machines are as optimized as, say, the Self environment (which reaches half the speed of optimized C!), they do perform some optimizations on Smalltalk code which make them run many times faster than a naive bytecode interpreter. Peter Deutsch, who among other things invented the idea of a just-in-time compiler like those you are used to seeing for Java45, once observed that implementing a language like Smalltalk efficiently requires the implementor to cheat... but that’s okay as long as you don’t get caught. That is, as long as you don’t break the language semantics. Let’s look at some of these optimizations.

For certain frequently used ’special selectors’, the compiler emits a send-special-selector bytecode instead of a send-message bytecode. Special selectors have one of three behaviors:

No-lookup methods do contain a primitive number specification, <primitive: xx>, but it is used only when the method is reached through a #perform:… message send. Since the method is not normally looked up, deleting the primitive name specification cannot in general prevent this primitive from running. No-lookup pairs are listed below:

Integer/Integer
Float/Integer
Float/Float
 
for
 
+ - * = ~= > < >= <=
Integer/Integerfor// \\ bitOr: bitShift: bitAnd:
Any pair of objectsfor== isNil notNil class
BlockClosureforvalue value: blockCopy:46

Other messages are open coded by the compiler. That is, there are no message sends for these messages—if the compiler sees blocks without temporaries and with the correct number of arguments at the right places, the compiler unwinds them using jump bytecodes, producing very efficient code. These are:

  to:by:do: if the second argument is an integer literal
  to:do:
  timesRepeat:
  and:, or:
  ifTrue:ifFalse:, ifFalse:ifTrue:, ifTrue:, ifFalse:
  whileTrue:, whileFalse:

Other minor optimizations are done. Some are done by a peephole optimizer which is ran on the compiled bytecodes. Or, for example, when GNU Smalltalk pushes a boolean value on the stack, it automatically checks whether the following bytecode is a jump (which is a common pattern resulting from most of the open-coded messages above) and combines the execution of the two bytecodes. All these snippets can be optimized this way:

  1 to: 5 do: [ :i | … ]
  a < b and: [ … ]
  myObject isNil ifTrue: [ … ]

That’s all. If you want to know more, look at the virtual machine’s source code in libgst/interp-bc.inl and at the compiler in libgst/comp.c.


Footnotes

(45)

And like the one that GNU Smalltalk includes as an experimental feature.

(46)

You won’t ever send this message in Smalltalk programs. The compiler uses it when compiling blocks.


Previous: , Up: Behind the scenes