> 
> So just run an image with the simulator and stop at any of commonSend, 
> internalFindNewMethod, lookupMethodInClass: and you'll see the call chain 
> form the relevant send bytecode.
> 
> Here's an expression that loads and runs an image with the StackInterpreter:

cool I will see if I can show that during my lecture.

> 
> | vm |
> StackInterpreter initializeWithOptions: (Dictionary newFromPairs: #()).
> vm := StackInterpreterSimulator new.
> vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
> vm openAsMorph; run
> 
> and if you break on entry to internalFindNewMethod you'll see this stack:
> 
> StackInterpreterSimulatorLSB(Object)>>break
> StackInterpreterSimulatorLSB(StackInterpreter)>>internalFindNewMethod
> StackInterpreterSimulatorLSB(StackInterpreterSimulator)>>internalFindNewMethod
> StackInterpreterSimulatorLSB(StackInterpreter)>>commonSend
> StackInterpreterSimulatorLSB(StackInterpreterSimulator)>>commonSend
> StackInterpreterSimulatorLSB(StackInterpreter)>>normalSend
> StackInterpreterSimulatorLSB(StackInterpreter)>>secondExtendedSendBytecode
> StackInterpreterSimulatorLSB(StackInterpreterSimulator)>>dispatchOn:in:
> StackInterpreterSimulatorLSB(StackInterpreterSimulator)>>run
> UndefinedObject>>DoIt
> 
> If you find out what the selector is (e.g. self printOop: messageSelector) 
> you can then use the simulator;s own breakpoint facilities:
> 
> | vm |
> StackInterpreter initializeWithOptions: (Dictionary newFromPairs: #()).
> vm := StackInterpreterSimulator new.
> vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
> vm setBreakSelector: #&.
> vm openAsMorph; run
> 
> and now it'll stop in sendBreak:point:receiver: and you'll get this stack:
> 
> StackInterpreterSimulatorLSB(Object)>>halt:
> StackInterpreterSimulatorLSB(StackInterpreterSimulator)>>sendBreak:point:receiver:
> StackInterpreterSimulatorLSB(StackInterpreter)>>commonSend
> StackInterpreterSimulatorLSB(StackInterpreterSimulator)>>commonSend
> StackInterpreterSimulatorLSB(StackInterpreter)>>normalSend
> StackInterpreterSimulatorLSB(StackInterpreter)>>secondExtendedSendBytecode
> StackInterpreterSimulatorLSB(StackInterpreterSimulator)>>dispatchOn:in:
> StackInterpreterSimulatorLSB(StackInterpreterSimulator)>>run
> UndefinedObject>>DoIt
>>> - what is the invariant? 
>>>     that currentclass always point to the currently looked up class and 
>>>     newMethod is the found method?
>> 
>> 
>> The input arguments are messageSelector, argumentCount and its argument, 
>> class.  The VM suffers somewhat from being cluttered with global variables, 
>> which is I think a legacy of the blue-book specification (the Smalltalk code 
>> that was used to implement Interpreter in VMMaker) being derived from the 
>> Alto and Dorado implementations in microcode.  It would be nicer if there 
>> were fewer variables, but e.g. supplying argumentCount as a parameter 
>> throughout all the message handling routines can be difficult, especially 
>> when things like perform: and MNU change the argumentCount during message 
>> send.
> 
> I clearly see what you mean. 
> 
>>> - why lookupMethodFor: selector InDictionary: dictionary is defined in 
>>> StackInterpreter but never used
>>> only in CoInterpreter?
>> 
>> 
>> Well, it belongs in StackInterpreter and could be used in the other lookup 
>> methods.  I was probably considering rewriting the other lookup routines to 
>> use  lookupMethodFor: InDictionary: but didn't get round to it.
> 
> ok I see.
> 
> While reading directly the see code I was wondering why you generate the 
> ifdef for different bytecode set?
> Is it that you would have to call another object and that it would not have 
> the same instance variables.
> Because I was thinking that such variation points could be handled by the 
> different interpreter subclasses.
> 
> Bytecode dispatch is performance-critical in the context and stack 
> interpreters.  The ifdef means that if one is not using multiple bytecode 
> sets dispatch is simpler and hence faster.
> 
> Subclassing is very difficult because the simulators are not traits and so 
> subclass each interpreter class.  hence adding a subclass to handle this 
> difference means adding another simulator, and they're big and tedious to 
> maintain.  IMO the multiple bytecode set work just isn't worth that kind of 
> load.  The VM would be nicer if more fully decomposed.  I've done a fair 
> amount (moving the objectMemory into an instance variable, putting the Cogit 
> in its own class hierarchy, adding support for struct classes that define 
> data types like a stack page or an abstract instruction or machine-code 
> method in the JIT) but there's always more that one can do.
> 
> cheers!
>>> Thanks
>>> 
>>> 
>>> lookupMethodInClass: class
>>>     | currentClass dictionary found |
>>>     <inline: false>
>>>     self assert: class ~= objectMemory nilObject.
>>>     currentClass := class.
>>>     [currentClass ~= objectMemory nilObject]
>>>             whileTrue:
>>>             [dictionary := objectMemory fetchPointer: MethodDictionaryIndex 
>>> ofObject: currentClass.
>>> 
>>>             *** trick with the cannotInterpret ***
>>>             dictionary = objectMemory nilObject ifTrue:
>>>                     ["MethodDict pointer is nil (hopefully due a swapped 
>>> out stub)
>>>                             -- raise exception #cannotInterpret:."
>>>                     self createActualMessageTo: class.
>>>                     messageSelector := objectMemory splObj: 
>>> SelectorCannotInterpret.
>>>                     self sendBreak: messageSelector + BaseHeaderSize
>>>                             point: (objectMemory lengthOf: messageSelector)
>>>                             receiver: nil.
>>>                     ^self lookupMethodInClass: (self superclassOf: 
>>> currentClass)].
>>>             *** trick with the cannotInterpret end ***
>>> 
>>>             found := self lookupMethodInDictionary: dictionary.
>>>             found ifTrue: [^currentClass].
>>>                     ^^^^^^^^^^^^^^^^^^^^^^^^^
>>> 
>>>             currentClass := self superclassOf: currentClass].
>>> 
>>>     "Could not find #doesNotUnderstand: -- unrecoverable error."
>>>     messageSelector = (objectMemory splObj: SelectorDoesNotUnderstand) 
>>> ifTrue:
>>>             [self error: 'Recursive not understood error encountered'].
>>> 
>>>     "Cound not find a normal message -- raise exception #doesNotUnderstand:"
>>>     self createActualMessageTo: class.
>>>     messageSelector := objectMemory splObj: SelectorDoesNotUnderstand.
>>>     self sendBreak: messageSelector + BaseHeaderSize
>>>             point: (objectMemory lengthOf: messageSelector)
>>>             receiver: nil.
>>>     ^self lookupMethodInClass: class
>>> 
>>> 
>>> if (found) {
>>>     return currentClass;
>>>     }
>>> 
>>> 
>>> static sqInt
>>> lookupMethodInClass(sqInt class)
>>> {
>>>     // StackInterpreter>>#lookupMethodInClass:   DECL_MAYBE_SQ_GLOBAL_STRUCT
>>>     sqInt currentClass;
>>>     sqInt dictionary;
>>>     sqInt found;
>>>     sqInt header;
>>>     sqInt index;
>>>     sqInt length;
>>>     sqInt mask;
>>>     sqInt methodArray;
>>>     sqInt nextSelector;
>>>     sqInt sz;
>>>     sqInt wrapAround;
>>> 
>>>     assert(class != (nilObject()));
>>>     currentClass = class;
>>>     while (currentClass != GIV(nilObj)) {
>>> dictionary = longAt((currentClass + BaseHeaderSize) + 
>>> (MethodDictionaryIndex << ShiftForWord));
>>>             if (dictionary == GIV(nilObj)) {
>>> 
>>>                     /* ifTrue: */
>>> 
>>> createActualMessageTo(class);
>>>                     GIV(messageSelector) = longAt((GIV(specialObjectsOop) + 
>>> BaseHeaderSize) + (SelectorCannotInterpret << ShiftForWord));
>>>                     sendBreakpointreceiver(GIV(messageSelector) + 
>>> BaseHeaderSize, lengthOf(GIV(messageSelector)), null);
>>>                     return lookupMethodInClass(longAt((currentClass + 
>>> BaseHeaderSize) + (SuperclassIndex << ShiftForWord)));
>>>             }
>>>             /* begin lookupMethodInDictionary: */
>>> /* begin fetchWordLengthOf: */
>>> /* begin sizeBitsOf: */
>>> header = longAt(dictionary);
>>>             sz = ((header & TypeMask) == HeaderTypeSizeAndClass
>>>                     ? (longAt(dictionary - (BytesPerWord * 2))) & 
>>> LongSizeMask
>>>                     : header & SizeMask);
>>>             length = ((usqInt) (sz - BaseHeaderSize)) >> ShiftForWord;
>>>             mask = (length - SelectorStart) - 1;
>>> 
>>>             /* messageSelector */
>>> 
>>> index = SelectorStart + (mask & (((GIV(messageSelector) & 1)
>>>     ? (GIV(messageSelector) >> 1)
>>>     : (((usqInt) (longAt(GIV(messageSelector)))) >> HashBitsOffset) & 
>>> HashMaskUnshifted)));
>>>             wrapAround = 0;
>>>             while (1) {
>>> nextSelector = longAt((dictionary + BaseHeaderSize) + (index << 
>>> ShiftForWord));
>>>                     if (nextSelector == GIV(nilObj)) {
>>> found = 0;
>>>                             goto l1;
>>>                     }
>>>                     if (nextSelector == GIV(messageSelector)) {
>>> methodArray = longAt((dictionary + BaseHeaderSize) + (MethodArrayIndex << 
>>> ShiftForWord));
>>>                             GIV(newMethod) = longAt((methodArray + 
>>> BaseHeaderSize) + ((index - SelectorStart) << ShiftForWord));
>>>                             found = 1;
>>>                             goto l1;
>>>                     }
>>>                     index += 1;
>>>                     if (index == length) {
>>> if (wrapAround) {
>>> found = 0;
>>>                                     goto l1;
>>>                             }
>>>                             wrapAround = 1;
>>>                             index = SelectorStart;
>>>                     }
>>>             }
>>> found = 0;
>>>     l1:     /* end lookupMethodInDictionary: */;
>>>             if (found) {
>>> return currentClass;
>>>             }
>>>             currentClass = longAt((currentClass + BaseHeaderSize) + 
>>> (SuperclassIndex << ShiftForWord));
>>>     }
>>> if (GIV(messageSelector) == (longAt((GIV(specialObjectsOop) + 
>>> BaseHeaderSize) + (SelectorDoesNotUnderstand << ShiftForWord)))) {
>>>             error("Recursive not understood error encountered");
>>>     }
>>>     createActualMessageTo(class);
>>>     GIV(messageSelector) = longAt((GIV(specialObjectsOop) + BaseHeaderSize) 
>>> + (SelectorDoesNotUnderstand << ShiftForWord));
>>>     sendBreakpointreceiver(GIV(messageSelector) + BaseHeaderSize, 
>>> lengthOf(GIV(messageSelector)), null);
>>>     return lookupMethodInClass(class);
>>> }
>>> 
>>> 
>>> 
>>> 
>> 
>> 
>> 
>> 
>> -- 
>> best,
>> Eliot
> 
> 
> 
> 
> -- 
> best,
> Eliot

Reply via email to