On Wed, Feb 13, 2013 at 12:11 PM, Eliot Miranda <eliot.mira...@gmail.com>wrote:

> Hi Stef,
>
> On Wed, Feb 13, 2013 at 11:40 AM, Stéphane Ducasse <
> stephane.duca...@inria.fr> wrote:
>
>> I repost the mail to the mailing-list since I do not see it in the vm-dev
>>
>
> did you post to vm-dev?
>
>
>>
>> Stef
>>
>>
>> Hi
>>
>> I was reading the following method in the VM code and I have a couple of
>> questions:
>>
>> - I do not understand why lookupMethodInClass: may return a class. I was
>> thinking that it would return a method.
>>
>>
> It doesn't matter what it returns as it's return value is always ignored.
>  It assigns to newMethod.  I suspect it returns currentClass because a) the
> return type was always sqInt because Slang didn't support void functions,
> and b) currentClass is a value in hand so probably in a register and hence
> cheap to return.
>
>
>> - 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.
>

and so argumentCount must be the number of objects on the stack minus one,
messageSelector must be an object (any object).  The argument "class" must
be a behavior-like object that is on a list of behavior-like objects linked
through the superclass field that terminates with nil.  Each object on the
chain must have either nil or a method dictionary-like object in its method
dictionary.


> - 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.
>
>
>> 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