pharo-project / pharo

Pharo is a dynamic reflective pure object-oriented language supporting live programming inspired by Smalltalk.
http://pharo.org
Other
1.19k stars 353 forks source link

SystemNavigation default allUnimplementedCalls size -> DNU #9777

Closed Ducasse closed 2 years ago

Ducasse commented 3 years ago

executing the following expression SystemNavigation default allUnimplementedCalls size produces an error.

Ducasse commented 3 years ago

when doing meth messages we get a GlobalVariable????

Ducasse commented 3 years ago
(WidgetExample class>>#exampleBasicControls) messages

>>>
(#isDefault: #newListFor:list:selected:changeSelected:help: #minHeight: #vResizing: #useDefaultOKButton #newEditableDropListFor:list:getSelected:setSelected:addToList:ghostText:getEnabled:help: #newRow: #value: #red #'->' #newPluggableDialogWindow: #contentMorph: #openModal #newCheckboxFor:getSelected:setSelected:label:help: #wheel: #newMorphDropListFor:list:getSelected:setSelected:help: #extent: #newMorphListFor:list:getSelected:setSelected:help: #newLabel: #newTreeFor:list:selected:changeSelected: #@ #newButtonFor:getState:action:arguments:getEnabled:label:help: #NewValueHolder->NewValueHolder #newVerticalSeparator #builder #newTitle:for: #with: #newDropListFor:list:getSelected:setSelected:help: #newTextEditorFor:getText:setText: #newColumn: #newTextEntryFor:getText:setText:help: #currentWorld #minWidth: #setSelectedIndex: #newButtonFor:action:label:help: #newLabelGroup: #collect: #newSliderFor:getValue:setValue:help: #items: #new #disable #model: #color: #newRadioButtonFor:getSelected:setSelected:label:help:)
Ducasse commented 3 years ago

In P9 and P10

Ducasse commented 3 years ago
(WidgetExample class>>#exampleBasicControls) localMessages
Ducasse commented 3 years ago
addSelectorTo: set 
    "If this instruction is a send, add its selector to set."

    | selectorOrSelf |
    (selectorOrSelf := self selectorToSendOrSelf) == self ifFalse:
        [set add: selectorOrSelf]

is adding global variable.

Ducasse commented 3 years ago

Bingo, (WidgetExample class>>#exampleBasicControls) localMessages breaks

addSelectorTo: set 
    "If this instruction is a send, add its selector to set."

    | selectorOrSelf |
    (selectorOrSelf := self selectorToSendOrSelf) == self ifFalse:
        [
        selectorOrSelf class = GlobalVariable 
            ifTrue: [ self halt. ].
        set add: selectorOrSelf ]
Ducasse commented 3 years ago

A possible solution (not sure that it solves the real problem) is:

addSelectorTo: set 
    "If this instruction is a send, add its selector to set."

    | selectorOrSelf |
    (selectorOrSelf := self selectorToSendOrSelf) isSymbol ifTrue:
        [ set add: selectorOrSelf ]
guillep commented 3 years ago

There is something fishy with how the scanning is working. Tthe bytecode that gives the Global is at pc 1409 but if you look at the method 1409 is not a valid pc :)

image

It jumps from 1407 to 1413, because bytes 1407 + 1408 are an extension. The bytecode at 1409 is a valid bytecode, it is a send! But, if it is interpreted without the extension (which is what happens here), then the wrong literal index is used and some other random literal is taken instead of the correct selector, which in this case happened to be a global variable but it could have been anything ^^.

So, to reproduce it simply:

set := Set new.
s := InstructionStream new
    method: (WidgetExample class>>#exampleBasicControls)
    pc: 1409.
s addSelectorTo: set.
set

Now this means that evaluating/scanning bytecode 1407 does not properly advance the pc, and this is because scanFor: advances using bytecodeSize:

scanFor: scanBlock
    "Check all bytecode instructions with scanBlock, answer true if scanBlock answers true.
    This can be used to, e.g., check whether a method contains 'push closure' bytecodes like this:
    aMethod scanFor: [ :b | b = 143 ]"

    | method encoderClass end byte |
    method := self method.
    end := method endPC.
    encoderClass := method encoderClass.
    [pc <= end] whileTrue: 
        [(scanBlock value: (byte := method at: pc)) ifTrue:
            [^true].
         pc := pc + (encoderClass bytecodeSize: byte)].
    ^false

which does not take into account extensions :slight_smile:. Instead, scanFor: to work properly should do an abstract interpretation of the bytecode, check if it is an extension, and advance the whole block of bytecodes, not only the extension.

This should do it

scanFor: scanBlock

    "Check all bytecode instructions with scanBlock, answer true if scanBlock answers true.
    This can be used to, e.g., check whether a method contains 'push closure' bytecodes like this:
    aMethod scanFor: [ :b | b = 143 ]"

    | method encoderClass end byte |
    method := self method.
    end := method endPC.
    encoderClass := method encoderClass.
    [ pc <= end ] whileTrue: [ 
        (scanBlock value: (byte := method at: pc)) ifTrue: [ ^ true ].
        "Skip all the extensions and the current extended bytecode altogether"
        [ encoderClass isExtension: byte ] whileTrue: [ 
            pc := pc + (encoderClass bytecodeSize: byte).
            byte := method at: pc ].
        pc := pc + (encoderClass bytecodeSize: byte) ].
    ^ false

Not clear to me if this is the only place this could happen. What I'm almost sure is that extension bytecodes should be the only ones with this kind of behaviour ^^

guillep commented 3 years ago

Checking senders of bytecodeSize: shows that at least nextPc: should be updated too.

image

and maybe the bug should be only fixed in nextPc: and make scanFor: use nextPc: seems like a good call

guillep commented 3 years ago

And checking senders of nextPc: shows that we should be careful with pcInOuter that does a lot of manual things

guillep commented 3 years ago

(and!! nextPc: aBytecode is conceptually wrong in the presence of extensions :) )

nextPc to be correct should only receiver a pc/position. Because if it is an extension it must look ahead the following bytecodes, which we cannot do without the PC.

Ducasse commented 3 years ago

Thanks guille. I will put a pointer to the next issue. And I checked it in Pharo 90 because I wanted to make sure that it was not due to our changes. And to me it is not.

Ducasse commented 3 years ago

Now to me this is scary and I wonder why we do not get more bugs :)

guillep commented 3 years ago

Now to me this is scary and I wonder why we do not get more bugs :)

Because extended sends are used in veeeeery large methods with tons of literals. If you check the offending method, that is the case, but that is not a common pharo method :)

Ducasse commented 3 years ago

Yes! This is the conclusion I got.