- 
                Notifications
    You must be signed in to change notification settings 
- Fork 81
How does the bytecode interpreter work?
When we write a program in Pharo, that code gets translated to a specific series of bytecodes. Then those bytecodes are consumed by the interpreter, which you can think of basically as a giant fascinating switch-statement in C, where each bytecode will fall in one of the cases and then execute some code corresponding to the implementation of that specific bytecode.
For example if we have this Pharo method:
bar
   ^ 1+9
The first step in the execution of this method is the generation of bytecodes from it.
The generated bytecodes from the bar method will be the following:
<51> pushConstant: 1
<20> pushConstant: 9
<60> send: +
<5C> returnTop
The interpreter is a stack-machine, so we operate on it by manipulating a stack. Keep in mind that the actual bytecodes are those between < >. The text beside is only for us, the programmers. And also that these values are in hexadecimal, that's why you may see letters on them.
There we can see that it's pushing the two numbers on the stack and then sending a message to add them. This addition is performed by poping the two numbers off the stack and then pushing the result of adding them. Then, at the end it returns the top of the stack, where will be the result of the addition.
The calling convention of the intepreter is as follows:
- The caller pushes the arguments.
- The callee pops the arguments and then pushes the result.
The first element that gets pushed will always be the receiver of the message. And then, the arguments of the method, if any. These will get pushed in the same order as they appear. For example:
    myInstance baz: arg1 with: arg2
Inside the implementation of 'baz:with:', the stack will look something like this:
|   rcvr   |  
|   arg1   |
|   arg2   |   <- stack pointer
So we would access:
- arg2 as stack[0]
- arg2 as stack[1]
- rcvr as stack[3]
[The component that is responsible for translating from Pharo code to bytecodes is the Opal compiler]
Let's dig deeper in how the addition is permormed:
How can we understand what the <60> send: + bytecode is doing?
Well, we have the actual bytecode value: 60 (Remember that this value is in hex!)
Where can we search for it to get to the corresponding implementation?
We can do this by going to the 'bytecode initialization table'. This table is in the StackInterpreter >> initializeBytecodeTableForSistaV1 method.
There we can see all the mappings between bytecodes and their implementations. You can think of it as a Dictionary, where each key is the actual bytecode and each value is the corresponding implementation. Here the "keys" are in decimal notation, so to look for our 16r60 we have to convert it first. 16r60 is 10r96.
In the 96 position we see the method to call when the intepreter finds the bytecode 96: bytecodePrimAdd.
So, when the interpreter is executing the bytecode of a method, if it sees a send: + it will then call bytecodePrimAdd.
The implementation of this method is based on a prediction that on most of the send: + encountered, there will be two numbers to be added. Of course, as Pharo is a very dinamic language, this message + can be sent to any kind of objects, but bytecodePrimAdd is implemented thinking that most of the time the arguments will be just numbers.
So, if the arguments are in fact numbers (integers or floats) then the addition is performed very quickly.
If they are not numbers or if the result overflows, then a "normal send" is performed. This means that the + message will be handled like every other message, doing a lookup in the hierarchy of the receiver class and then when found it invoking it.
First, to invoke a method a message has to be sent to an object. So in the bytecodes we have to have a send:.
That send message is what would end up invoking a given method. The method to invoke will be given in the bytecode itself too. In the textual representation will be the name after the colon.
In the bytecode itself will be encoded in some way. The important thing is that we can know what method to invoke just from the bytecode.
We have the method to invoke. In fact, what we have is the "selector" of the method to invoke. This is a string, that we are guaranteed to be unique, that corresponds to the method. We have to look for the implementation of this method. Where do we look for it?
If we do something like this:
n := someArray size
We expect that the instance someArray knows how to answer the size message.
To do that, it must implement the size method. That implementation will be installed in the Array class, this way all Array instances will know how to answer the size method.
Long story short, the implementation of the method must be in the class of the receiver (The receiver is the object that we are sending the message to).
Then, to actually invoke a method we need to look up the implementation of it (by using the selector) in the class of the receiver, if it's not found there, then we go to the superclass of the receiver, all the way up the hierarchy. This is what is called a 'look-up', whenever we want to avoid doing it, it may be a little slow to traverse all the hierarchy of a class.
As we have said earlier, the message itself is encoded in some way in the actual bytecode. There are different kind of 'send' bytecodes.
If we go again to the table in the StackInterpreter >> initializeBytecodeTableForSistaV1 method, we can see that there are a couple of bytecodes that start with 'send'.
We will explore them shortly after, but first: Those are not the only bytecodes corresponding to 'send's.
For example, take this very simple Pharo method:
bar
	| arr |
	
	arr := Array new: 10.
	
	^ arr
The generated bytecode will be:
<10> pushLit: Array
<21> pushConstant: 10
<7D> send: new:
<D0> popIntoTemp: 0
<40> pushTemp: 0
<5C> returnTop
[To see the bytecodes of a method, open the method in the Browser and then righ-click the method -> Extra -> Inspect . Or cmd+i directly. This will open an Inspector window, with a couple of tabs. Click on the Bytecode tab.]
Let's focus on the send: bytecode. Here we are sendig the new: message.
If we look for 7D (in decimal: 125) in the table we see that the implementation is in a method called bytecodePrimNewWithArg, it's not in method that starts with send!
Well there are special cases, like we saw earlier with the addition, that are handled separetely. Of course they are still a message send!
[
In the previous bytecode we can see clearly how the interpreter works when sending messages that take arguments. We are sending the new: message to the Array class, and we give it the argument by pushing it onto the stack. The implementation of the new: method expects that at the top of the stack will be the argument.
]
There are a lot of special cases like this, if we open the initialization table we can see that from "keys" 96 to 127 are all for 'special selectors'.
But if we see past 127, we see:
                (128 143	sendLiteralSelector0ArgsBytecode)
		(144 159	sendLiteralSelector1ArgBytecode)
		(160 175	sendLiteralSelector2ArgsBytecode)
These ones are a little more general. They don't work for a specific 'hardcoded' selector. Instead, they work with a selector that is set on the 'literals table'.
Remember when we said earlier that the (Opal) compiler generates bytecode from the Pharo code? Well, actually it generates an CompiledMethod object.
These kind of objects are what the Pharo virtual machine knows how to execute. They have a specific layout in memory:
 
So, whenever Opal compiles some Pharo code, it will generate an object that looks like the diagram. It will have a header that describes the compiled code.
And then it will have a variable amount of literals.
The literals will be any constant value that the compiled code will need to access to execute correctly.
For example, if one of the bytecodes it's a push 999 then that value 999 will be as a literal, and then when the code wants to access it, it will go the this 'table of literals' that is inside the CompiledMethod. The value 999 will be at a certain (known) offset.
Even the strings that are part of the method will be as literals, like the selector and the class of the receiver.
This 'table of literals' will be built when the method is compiled. Then the generated bytecodes will reference it whenever it has to access some literal.
[For more information about `CompiledMethod`, refer to the Class Comment in the Pharo image. Also, check `CompiledCode`, its superclass]
End small diversion.
If you understand how this method works then sendLiteralSelector1ArgBytecode and sendLiteralSelector2ArgBytecode should be no problem.
The 3 are very similar, the only difference is the number of arguments they expect.
First, looking at the initialization table we see that this method corresponds to a range of values, not only one:
    (128 143	sendLiteralSelector0ArgsBytecode)
What is happening here is that this method can access any of the first 16 literals that are defined in the 'table of literals' of the CompiledMethod, as we saw earlier.
128 is in decimal, if we view it as hex it's: 16r80 
143 is 16r8F
Viewing them as binary we get:
 
So, we have 16 ways to invoke the sendLiteralSelector0ArgsBytecode method, from 128 to 143.
If we look close to the binary representation of each value we see that the most significant nibble (upper 4 bits) is always the same (1000). Each value differs only in the least significant nibble. As we have 4 bits for that then the number of different values will be 16 (0 through 15).
Let's take a look at the actual implementation:
sendLiteralSelector0ArgsBytecode
	| rcvr |
	messageSelector := self literal: (currentBytecode bitAnd: 16rF).
	argumentCount := 0.
	rcvr := self stackValue: 0.
	lkupClassTag := objectMemory fetchClassTagOf: rcvr.
	self assert: lkupClassTag ~= objectMemory nilObject.
	self commonSendOrdinary
In the first line we get the selector of the message. As said earlier, this selector is a literal of the method. So to access it we use an offset. The value of this offset will be given by the bytecode itself. It will be encoded in the least significant nibble. That's why we can access any of the 16 first literals, because we have only 4 bits to encode its index!
To access those 4 bits we 'bit and' the bytecode with 16rF. This works because 16rF is just 1111.
For example:

Then, as we are in sendLiteralSelector0ArgsBytecode the number of arguments is 0, so we set argumentCount to 0.
You may be wondering why is this? Why bother setting this up? Why can't the interpreter infer it from the name of the method?
This is because of how the commonSendOrdinary works. We'll see it shortly.
Then we set the receiver of the message. As no argument was pushed to the stack, we can access to the receiver was just looking at the top of the stack.
The receiver itself will be an instance, so to correctly perform the look-up we have to access to the class of the receiver. We do that with the method fetchClassTagOf:. Then we check that said class exists, that is, that is not nil.
Finally we perform the look-up of the method. We do this by using the method commonSendOrdinary.
This method is pretty complex but if we open it, we can read its comment and understand pretty well what it's doing:
commonSendOrdinary
	"Send a message, starting lookup with the receiver's class."
	"Assume: messageSelector and argumentCount have been set, and that 
	the receiver and arguments have been pushed onto the stack,"
	"Note: This method is inlined into the interpreter dispatch loop."
	<sharedCodeInCase: #extSendBytecode>
	self sendBreakpoint: messageSelector receiver: (self stackValue: argumentCount).
	self doRecordSendTrace.
	self findNewMethodOrdinary.
	self executeNewMethod: false.
	self fetchNextBytecode
Look at the assumption it makes, and then check again the implementation of sendLiteralSelector0ArgsBytecode. Everything is set just as commonSendOrdinary expects it.
In this case we don't have any arguments (we are looking at sendLiteralSelector0ArgsBytecode!) but if we take sendLiteralSelector1ArgsBytecode, in this case we would have
one argument. And commonSendOrdinary expects it to be pushed. So, the bytecode instruction before the send: should be a 'push' that pushes the (only) argument.
What can we do if we would like to see some concrete real examples of usage of sendLiteralSelector0ArgsBytecode?
This is, real examples where the generated bytecode list contains some bytecode with any values between 128 and 143. How can we search for that?
Even more, as we are doing this for pedagogical reasons we would like to focus on "simple" methods, of course the defition of simple can vary but a good approach could be to look only for "short" methods (again this definition is a little subjective, but let's say that a method is short if its number of bytecodes is less or equal than 10).
This way we can concentrate on the send:s messages :)
We can do it with a simple code like this:
results := OrderedCollection new. CompiledMethod allInstancesDo: [ :method | (method bytecodes size <= 10 and: [method bytecodes includesAny: (128 to: 143)]) ifTrue: [ results add: method ] ].
If we execute this on a Playground, then inspect the variable results we can see a long list of methods. Any of these would be a good example of sendLiteralSelector0ArgsBytecode.
We saw that when sendLiteralSelector0ArgsBytecode executes, the messageSelector is obtained from the literals table.
Who built that table? When did it get built?
Find out in the next episode!
[Spoiler: EncoderForSistaV1 >> genSend:numArgs:]
- Compiling and repo organization
- Participate!
- Misc