[Vm-dev] VM Maker: VMMaker.oscog-eem.281.mcz

Igor Stasenko siguctua at gmail.com
Wed Apr 3 23:37:11 UTC 2013


On 4 April 2013 00:37, Eliot Miranda <eliot.miranda at gmail.com> wrote:
> Guys, please integrate this asap.  This is a horrible bug that is probably
> causing all sorts of crashes in large images on linux, and should have been
> generally causing horrible crashes all over the place.  Bugs are good at
> lurking :-/.
>

Glad we have less and less of them. Thanks for your effort, Eliot!

I am currently at some remote place in Switzerland ;) , and cannot do
much right now..
We're also have an interesting bug with pharo VM which (i guess)
related to some stack (mis)balancing,
we have a reproducible case where running code given you SmallInteger>>DNU...
because some SmallInteger pops up on the stack at some point. At least
it doesn't causing VM crash.
But i had no time to investigate that. Esteban, do you having any new
details on that?

>
> On Wed, Apr 3, 2013 at 3:27 PM, <commits at source.squeak.org> wrote:
>>
>>
>> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
>> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.281.mcz
>>
>> ==================== Summary ====================
>>
>> Name: VMMaker.oscog-eem.281
>> Author: eem
>> Time: 3 April 2013, 3:27:02.058 pm
>> UUID: 64be55df-6421-4087-a712-5c07419806c7
>> Ancestors: VMMaker.oscog-eem.280
>>
>> Cogit: Fix *HORRIBLE* yet ancient bug with the CogObjectRep.
>> Both CogObjectRepresentationForSqueakV3>>couldBeObject: &
>> CogObjectRepresentationForSqueakV3>>shouldAnnotateObjectReference:
>> used signed comparisons for oops and so once the heap size
>> pushes oops into the upper half of the address space constant
>> oops in machine code were no longer being updated by the GC.
>>
>> StackInterpreter: reqrite the login for printing methods so that
>> printing the frame of a bad receiver won't seg fault.
>>
>> =============== Diff against VMMaker.oscog-eem.280 ===============
>>
>> Item was changed:
>>   ----- Method: CogObjectRepresentationForSqueakV3>>couldBeObject: (in
>> category 'garbage collection') -----
>>   couldBeObject: oop
>>         ^(objectMemory isNonIntegerObject: oop)
>> +         and: [self oop: oop isGreaterThanOrEqualTo: objectMemory
>> nilObject]!
>> -         and: [oop asUnsignedInteger >= objectMemory nilObject]!
>>
>> Item was changed:
>>   ----- Method:
>> CogObjectRepresentationForSqueakV3>>shouldAnnotateObjectReference: (in
>> category 'garbage collection') -----
>>   shouldAnnotateObjectReference: anOop
>>         "self assert: ((objectMemory isIntegerObject: anOop)
>>                                 or: [objectMemory addressCouldBeObj:
>> anOop])."
>>         ^(objectMemory isNonIntegerObject: anOop)
>> +         and: [self oop: anOop isGreaterThan: objectMemory trueObject]!
>> -         and: [anOop > objectMemory trueObject]!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter class>>requiredMethodNames (in category
>> 'translation') -----
>>   requiredMethodNames
>>         "return the list of method names that should be retained for
>> export or other support reasons"
>>         | requiredList |
>>         requiredList := self exportAPISelectors.
>>         requiredList addAll: NewObjectMemory requiredMethodNames.
>>         "A number of methods required by VM support code, jitter, specific
>> platforms etc"
>>         requiredList addAll: #(
>>                 assertValidExecutionPointe:r:s:
>>                 characterForAscii: checkedLongAt:
>>                 delayExpired
>> +               findClassOfMethod:forReceiver: findSelectorOfMethod:
>> -               findClassOfMethod:forReceiver:
>> findSelectorOfMethod:forReceiver:
>>                         forceInterruptCheck
>> forceInterruptCheckFromHeartbeat fullDisplayUpdate
>>                 getCurrentBytecode getFullScreenFlag getInterruptKeycode
>> getInterruptPending
>>                         getSavedWindowSize getThisSessionID
>>                 highBit:
>>                 interpret
>>                 loadInitialContext
>>                 oopFromChunk:
>>                 primitiveFail primitiveFailFor:
>> primitiveFlushExternalPrimitives printAllStacks printCallStack printContext:
>>                         printExternalHeadFrame printFramesInPage:
>> printFrame: printHeadFrame printMemory printOop:
>>                                 printStackPages printStackPageList
>> printStackPagesInUse printStackPageListInUse
>>                 readableFormat: readImageFromFile:HeapSize:StartingAt:
>>                 setFullScreenFlag: setInterruptKeycode:
>> setInterruptPending: setInterruptCheckChain:
>>                         setSavedWindowSize: success:
>>                 validInstructionPointer:inMethod:framePointer:).
>>
>>         "Nice to actually have all the primitives available"
>>         requiredList addAll: (self primitiveTable select: [:each| each
>> isSymbol]).
>>
>>         "InterpreterProxy is the internal analogue of sqVirtualMachine.c,
>> so make sure to keep all those"
>>         InterpreterProxy organization categories do:
>>                 [:cat |
>>                 ((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue:
>>                         [requiredList addAll: (InterpreterProxy
>> organization listAtCategoryNamed: cat)]].
>>
>>         ^requiredList!
>>
>> Item was added:
>> + ----- Method: StackInterpreter>>addressCouldBeClassObj: (in category
>> 'debug support') -----
>> + addressCouldBeClassObj: maybeClassObj
>> +       "Answer if maybeClassObj looks like a class object"
>> +       <inline: false>
>> +       ^(objectMemory addressCouldBeObj: maybeClassObj)
>> +         and: [((objectMemory isPointersNonInt: maybeClassObj) and:
>> [(objectMemory lengthOf: maybeClassObj) >= 3])
>> +         and: [(objectMemory isPointersNonInt: (objectMemory
>> fetchPointer: SuperclassIndex ofObject: maybeClassObj))
>> +         and: [(objectMemory isPointersNonInt: (objectMemory
>> fetchPointer: MethodDictionaryIndex ofObject: maybeClassObj))
>> +         and: [(objectMemory isIntegerObject: (objectMemory fetchPointer:
>> InstanceSpecificationIndex ofObject: maybeClassObj))]]]]!
>>
>> Item was added:
>> + ----- Method: StackInterpreter>>findClassContainingMethod:startingAt:
>> (in category 'debug support') -----
>> + findClassContainingMethod: meth startingAt: classObj
>> +       | currClass classDict classDictSize methodArray i |
>> +       currClass := classObj.
>> +       [classDict := objectMemory fetchPointer: MethodDictionaryIndex
>> ofObject: currClass.
>> +        classDictSize := objectMemory fetchWordLengthOf: classDict.
>> +        methodArray := objectMemory fetchPointer: MethodArrayIndex
>> ofObject: classDict.
>> +        i := 0.
>> +        [i < (classDictSize - SelectorStart)] whileTrue:
>> +               [meth = (objectMemory fetchPointer: i ofObject:
>> methodArray) ifTrue:
>> +                       [^currClass].
>> +                i := i + 1].
>> +        currClass := self superclassOf: currClass.
>> +        currClass = objectMemory nilObject] whileFalse.
>> +       ^currClass              "method not found in superclass chain"!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter>>findClassOfMethod:forReceiver: (in
>> category 'debug support') -----
>>   findClassOfMethod: meth forReceiver: rcvr
>> +       | rclass |
>> +       (objectMemory addressCouldBeOop: rcvr) ifTrue:
>> +               [rclass := objectMemory fetchClassOf: rcvr.
>> +                (self addressCouldBeClassObj: rclass) ifTrue:
>> +                       [rclass := self findClassContainingMethod: meth
>> startingAt: rclass.
>> +                       rclass ~= objectMemory nilObject ifTrue:
>> +                               [^rclass]]].
>> -
>> -       | rclass currClass classDict classDictSize methodArray i |
>>         (objectMemory addressCouldBeObj: meth) ifFalse:
>>                 [^objectMemory nilObject].
>> +       ^self findClassContainingMethod: meth startingAt: (self
>> methodClassOf: meth)!
>> -       (objectMemory addressCouldBeOop: rcvr)
>> -               ifTrue: [rclass := objectMemory fetchClassOf: rcvr]
>> -               ifFalse: [rclass := self methodClassOf: meth].
>> -       currClass := rclass.
>> -       [classDict := objectMemory fetchPointer: MethodDictionaryIndex
>> ofObject: currClass.
>> -        classDictSize := objectMemory fetchWordLengthOf: classDict.
>> -        methodArray := objectMemory fetchPointer: MethodArrayIndex
>> ofObject: classDict.
>> -        i := 0.
>> -        [i < (classDictSize - SelectorStart)] whileTrue:
>> -               [meth = (objectMemory fetchPointer: i ofObject:
>> methodArray) ifTrue:
>> -                       [^currClass].
>> -                i := i + 1].
>> -        currClass := self superclassOf: currClass.
>> -        currClass = objectMemory nilObject] whileFalse.
>> -       ^rclass         "method not found in superclass chain"!
>>
>> Item was added:
>> + ----- Method: StackInterpreter>>findSelectorOfMethod: (in category
>> 'debug support') -----
>> + findSelectorOfMethod: meth
>> +       | classObj classDict classDictSize methodArray i |
>> +       (objectMemory addressCouldBeObj: meth) ifFalse:
>> +               [^objectMemory nilObject].
>> +       classObj := self methodClassOf: meth.
>> +       (self addressCouldBeClassObj: classObj) ifTrue:
>> +               [classDict := objectMemory fetchPointer:
>> MethodDictionaryIndex ofObject: classObj.
>> +                classDictSize := objectMemory fetchWordLengthOf:
>> classDict.
>> +                methodArray := objectMemory fetchPointer:
>> MethodArrayIndex ofObject: classDict.
>> +                i := 0.
>> +                [i <= (classDictSize - SelectorStart)] whileTrue:
>> +                       [meth = (objectMemory fetchPointer: i ofObject:
>> methodArray) ifTrue:
>> +                               [^(objectMemory fetchPointer: i +
>> SelectorStart ofObject: classDict)].
>> +                                i := i + 1]].
>> +       ^objectMemory nilObject!
>>
>> Item was removed:
>> - ----- Method: StackInterpreter>>findSelectorOfMethod:forReceiver: (in
>> category 'debug support') -----
>> - findSelectorOfMethod: meth forReceiver: rcvr
>> -
>> -       | currClass classDict classDictSize methodArray i |
>> -       (objectMemory addressCouldBeObj: meth) ifFalse:
>> -               [^objectMemory nilObject].
>> -       (objectMemory addressCouldBeOop: rcvr)
>> -               ifTrue: [currClass := objectMemory fetchClassOf: rcvr]
>> -               ifFalse: [currClass := self methodClassOf: meth].
>> -       [classDict := objectMemory fetchPointer: MethodDictionaryIndex
>> ofObject: currClass.
>> -        classDictSize := objectMemory fetchWordLengthOf: classDict.
>> -        methodArray := objectMemory fetchPointer: MethodArrayIndex
>> ofObject: classDict.
>> -        i := 0.
>> -        [i <= (classDictSize - SelectorStart)] whileTrue:
>> -               [meth = (objectMemory fetchPointer: i ofObject:
>> methodArray) ifTrue:
>> -                       [^(objectMemory fetchPointer: i + SelectorStart
>> ofObject: classDict)].
>> -                       i := i + 1].
>> -        currClass := self superclassOf: currClass.
>> -        currClass = objectMemory nilObject] whileFalse.
>> -       ^currClass    "method not found in superclass chain"!
>>
>> Item was changed:
>>   ----- Method:
>> StackInterpreter>>printActivationNameFor:receiver:isBlock:firstTemporary:
>> (in category 'debug printing') -----
>>   printActivationNameFor: aMethod receiver: anObject isBlock: isBlock
>> firstTemporary: maybeMessage
>> +       | methClass methodSel classObj |
>> -       | methClass methodSel |
>>         <inline: false>
>>         isBlock ifTrue:
>>                 [self print: '[] in '].
>>         methClass := self findClassOfMethod: aMethod forReceiver:
>> anObject.
>> +       methodSel := self findSelectorOfMethod: aMethod.
>> +       ((objectMemory addressCouldBeOop: anObject)
>> +        and: [self addressCouldBeClassObj: (classObj := objectMemory
>> fetchClassOf: anObject)])
>> -       methodSel := self findSelectorOfMethod: aMethod forReceiver:
>> anObject.
>> -       (objectMemory addressCouldBeOop: anObject)
>>                 ifTrue:
>> +                       [classObj = methClass
>> -                       [(objectMemory fetchClassOf: anObject) = methClass
>>                                 ifTrue: [self printNameOfClass: methClass
>> count: 5]
>>                                 ifFalse:
>> +                                       [self printNameOfClass: classObj
>> count: 5.
>> -                                       [self printNameOfClass:
>> (objectMemory fetchClassOf: anObject) count: 5.
>>                                          self print: '('.
>>                                          self printNameOfClass: methClass
>> count: 5.
>>                                          self print: ')']]
>>                 ifFalse: [self print: 'INVALID RECEIVER'].
>>         self print: '>'.
>>         (objectMemory addressCouldBeOop: methodSel)
>>                 ifTrue:
>>                         [methodSel = objectMemory nilObject
>>                                 ifTrue: [self print: '?']
>>                                 ifFalse: [self printStringOf: methodSel]]
>>                 ifFalse: [self print: 'INVALID SELECTOR'].
>>         (methodSel = (objectMemory splObj: SelectorDoesNotUnderstand)
>>         and: [(objectMemory addressCouldBeObj: maybeMessage)
>>         and: [(objectMemory fetchClassOf: maybeMessage) = (objectMemory
>> splObj: ClassMessage)]]) ifTrue:
>>                 ["print arg message selector"
>>                 methodSel := objectMemory fetchPointer:
>> MessageSelectorIndex ofObject: maybeMessage.
>>                 self print: ' '.
>>                 self printStringOf: methodSel]!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter>>selectorOfContext: (in category 'debug
>> printing') -----
>>   selectorOfContext: aContext
>>         (objectMemory isContext: aContext) ifFalse:
>>                 [^nil].
>> +       ^self findSelectorOfMethod: (objectMemory fetchPointer:
>> MethodIndex ofObject: aContext)!
>> -       ^self
>> -               findSelectorOfMethod: (objectMemory fetchPointer:
>> MethodIndex ofObject: aContext)
>> -               forReceiver:  (objectMemory fetchPointer: ReceiverIndex
>> ofObject: aContext)!
>>
>
>
>
> --
> best,
> Eliot



-- 
Best regards,
Igor Stasenko.


More information about the Vm-dev mailing list