On Mon, Jul 23, 2012 at 11:34 AM, Mariano Martinez Peck <
marianop...@gmail.com> wrote:

>
>
> On Mon, Jul 23, 2012 at 8:08 PM, Eliot Miranda <eliot.mira...@gmail.com>wrote:
>
>> Hi Marcel,
>>
>>     that's because the old hash method is broken.  The Cog VM finally
>> adds a correct bounds check that prevents byte access to the non-byte parts
>> (literals) of a CompiledMethod.  Accessing the literals of a method via
>> byte access gives access to the addresses of objects.  This is broken since
>> the GC is a moving garbage collector and so addresses can change.  Hence a
>> hash derived from such bytes is not stable.  See Kernel-eem.692 which
>> provides the attached hash method.
>>
>>
> Hi Eliot. I remember seeing this discussion in the Pharo mailing list
> also. So...I guess we should commit that also in Pharo, right?
>

Yes.  Also the bug fixes in Kernel-eem.700 & Kernel-eem.703.


>
>
>>
>> On Sun, Jul 22, 2012 at 7:10 AM, Marcel Taeumel <
>> marcel.taeu...@student.hpi.uni-potsdam.de> wrote:
>>
>>> Hi!
>>>
>>> It is not possible to compute the hash value of a CompiledMethod instance
>>> with the CogVM r2559 on a Windows 7 machine using a Squeak 4.3 image.
>>>
>>> Should it be possible despite of all enhancements in the Cog VM?
>>>
>>> Best,
>>> Marcel
>>>
>>> 22 July 2012 4:06:54.988 pm
>>>
>>> VM: Win32 - Smalltalk
>>> Image: Squeak4.3 [latest update: #11860]
>>>
>>> SecurityManager state:
>>> Restricted: false
>>> FileAccess: true
>>> SocketAccess: true
>>> Working Dir C:\Tools\vivide_dev
>>> Trusted Dir C:\Tools\vivide_dev\Marcel
>>> Untrusted Dir C:\Users\Marcel\Documents\My Squeak
>>>
>>> CompiledMethod(Object)>>error:
>>>         Receiver: (Morph>>#drawOn: "a CompiledMethod(337)")
>>>         Arguments and temporary variables:
>>>                 aString:        'subscript is out of bounds: 1'
>>>         Receiver's instance variables:
>>> (Morph>>#drawOn: "a CompiledMethod(337)")
>>>
>>> CompiledMethod(Object)>>errorSubscriptBounds:
>>>         Receiver: (Morph>>#drawOn: "a CompiledMethod(337)")
>>>         Arguments and temporary variables:
>>>                 index:  1
>>>         Receiver's instance variables:
>>> (Morph>>#drawOn: "a CompiledMethod(337)")
>>>
>>> CompiledMethod(Object)>>basicAt:
>>>         Receiver: (Morph>>#drawOn: "a CompiledMethod(337)")
>>>         Arguments and temporary variables:
>>>                 index:  1
>>>         Receiver's instance variables:
>>> (Morph>>#drawOn: "a CompiledMethod(337)")
>>>
>>> CompiledMethod class(ByteArray class)>>hashBytes:startingWith:
>>>         Receiver: CompiledMethod
>>>         Arguments and temporary variables:
>>>                 aByteArray:     (Morph>>#drawOn: "a CompiledMethod(337)")
>>>                 speciesHash:    244619647
>>>                 byteArraySize:  43
>>>                 hash:   244619647
>>>                 low:    nil
>>>                 pos:    1
>>>         Receiver's instance variables:
>>>                 superclass:     ByteArray
>>>                 methodDict:     a MethodDictionary(size 190)
>>>                 format:         3586
>>>                 instanceVariables:      nil
>>>                 organization:   ('accessing' clearFlag defaultSelector
>>> dragLabel endPC flag
>>> flush...etc...
>>>                 subclasses:     nil
>>>                 name:   #CompiledMethod
>>>                 classPool:      a Dictionary(#LargeFrame->56
>>> #SmallFrame->16 )
>>>                 sharedPools:    nil
>>>                 environment:    Smalltalk globals "a SystemDictionary
>>> with lots of globals"
>>>                 category:       #'Kernel-Methods'
>>>
>>> CompiledMethod(ByteArray)>>hash
>>>         Receiver: (Morph>>#drawOn: "a CompiledMethod(337)")
>>>         Arguments and temporary variables:
>>>
>>>         Receiver's instance variables:
>>> (Morph>>#drawOn: "a CompiledMethod(337)")
>>>
>>> UndefinedObject>>DoIt
>>>         Receiver: nil
>>>         Arguments and temporary variables:
>>>
>>>         Receiver's instance variables:
>>> nil
>>>
>>> Compiler>>evaluate:in:to:notifying:ifFail:logged:
>>>         Receiver: a Compiler
>>>         Arguments and temporary variables:
>>>                 textOrStream:   a ReadWriteStream '(Morph>>#drawOn:)
>>> hash'
>>>                 aContext:       nil
>>>                 receiver:       nil
>>>                 aRequestor:     a SmalltalkEditor
>>>                 failBlock:      [closure] in [] in
>>> SmalltalkEditor(TextEditor)>>evaluateSelectionAnd...etc...
>>>                 logFlag:        true
>>>                 methodNode:     DoIt
>>>         ^ (Morph >> #drawOn:) hash
>>>                 method:         (UndefinedObject>>#DoIt "a
>>> CompiledMethod(1506)")
>>>                 value:  nil
>>>                 toLog:  nil
>>>                 itsSelection:   nil
>>>                 itsSelectionString:     nil
>>>         Receiver's instance variables:
>>>                 sourceStream:   a ReadWriteStream '(Morph>>#drawOn:)
>>> hash'
>>>                 requestor:      a SmalltalkEditor
>>>                 class:  UndefinedObject
>>>                 category:       nil
>>>                 context:        nil
>>>                 parser:         a Parser
>>>
>>> [] in SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo:
>>>         Receiver: a SmalltalkEditor
>>>         Arguments and temporary variables:
>>> <<error during printing>
>>>         Receiver's instance variables:
>>>                 morph:  a TextMorphForEditView(2114)
>>>                 selectionShowing:       false
>>>                 model:  a Workspace
>>>                 paragraph:      a MultiNewParagraph
>>>                 markBlock:      a CharacterBlock with index 1 and
>>> character $( and rectangle
>>> 0@0 cor...etc...
>>>                 pointBlock:     a CharacterBlock with index 23 and
>>> rectangle 154@0 corner:
>>> 154@17
>>>  ...etc...
>>>                 beginTypeInIndex:       nil
>>>                 emphasisHere:   {a TextFontChange font: 1}
>>>                 lastParenLocation:      nil
>>>                 otherInterval:  (1 to: 22)
>>>                 oldInterval:    (1 to: 22)
>>>                 typeAhead:      a WriteStream ''
>>>                 styler:         nil
>>>
>>> BlockClosure>>on:do:
>>>         Receiver: [closure] in
>>> SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo:
>>>         Arguments and temporary variables:
>>>                 exception:      OutOfScopeNotification
>>>                 handlerAction:  [closure] in
>>> SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo...etc...
>>>                 handlerActive:  true
>>>         Receiver's instance variables:
>>>                 outerContext:
>>> SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo:
>>>                 startpc:        97
>>>                 numArgs:        0
>>>
>>> SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo:
>>>         Receiver: a SmalltalkEditor
>>>         Arguments and temporary variables:
>>>                 aBlock:         [closure] in
>>> SmalltalkEditor(TextEditor)>>evaluateSelection
>>>                 result:         nil
>>>                 rcvr:   nil
>>>                 ctxt:   nil
>>>         Receiver's instance variables:
>>>                 morph:  a TextMorphForEditView(2114)
>>>                 selectionShowing:       false
>>>                 model:  a Workspace
>>>                 paragraph:      a MultiNewParagraph
>>>                 markBlock:      a CharacterBlock with index 1 and
>>> character $( and rectangle
>>> 0@0 cor...etc...
>>>                 pointBlock:     a CharacterBlock with index 23 and
>>> rectangle 154@0 corner:
>>> 154@17
>>>  ...etc...
>>>                 beginTypeInIndex:       nil
>>>                 emphasisHere:   {a TextFontChange font: 1}
>>>                 lastParenLocation:      nil
>>>                 otherInterval:  (1 to: 22)
>>>                 oldInterval:    (1 to: 22)
>>>                 typeAhead:      a WriteStream ''
>>>                 styler:         nil
>>>
>>> SmalltalkEditor(TextEditor)>>evaluateSelection
>>>         Receiver: a SmalltalkEditor
>>>         Arguments and temporary variables:
>>>
>>>         Receiver's instance variables:
>>>                 morph:  a TextMorphForEditView(2114)
>>>                 selectionShowing:       false
>>>                 model:  a Workspace
>>>                 paragraph:      a MultiNewParagraph
>>>                 markBlock:      a CharacterBlock with index 1 and
>>> character $( and rectangle
>>> 0@0 cor...etc...
>>>                 pointBlock:     a CharacterBlock with index 23 and
>>> rectangle 154@0 corner:
>>> 154@17
>>>  ...etc...
>>>                 beginTypeInIndex:       nil
>>>                 emphasisHere:   {a TextFontChange font: 1}
>>>                 lastParenLocation:      nil
>>>                 otherInterval:  (1 to: 22)
>>>                 oldInterval:    (1 to: 22)
>>>                 typeAhead:      a WriteStream ''
>>>                 styler:         nil
>>>
>>> SmalltalkEditor(TextEditor)>>doIt
>>>         Receiver: a SmalltalkEditor
>>>         Arguments and temporary variables:
>>>
>>>         Receiver's instance variables:
>>>                 morph:  a TextMorphForEditView(2114)
>>>                 selectionShowing:       false
>>>                 model:  a Workspace
>>>                 paragraph:      a MultiNewParagraph
>>>                 markBlock:      a CharacterBlock with index 1 and
>>> character $( and rectangle
>>> 0@0 cor...etc...
>>>                 pointBlock:     a CharacterBlock with index 23 and
>>> rectangle 154@0 corner:
>>> 154@17
>>>  ...etc...
>>>                 beginTypeInIndex:       nil
>>>                 emphasisHere:   {a TextFontChange font: 1}
>>>                 lastParenLocation:      nil
>>>                 otherInterval:  (1 to: 22)
>>>                 oldInterval:    (1 to: 22)
>>>                 typeAhead:      a WriteStream ''
>>>                 styler:         nil
>>>
>>> SmalltalkEditor(TextEditor)>>doIt:
>>>         Receiver: a SmalltalkEditor
>>>         Arguments and temporary variables:
>>>                 aKeyboardEvent:         [keystroke '<Cmd-d>']
>>>         Receiver's instance variables:
>>>                 morph:  a TextMorphForEditView(2114)
>>>                 selectionShowing:       false
>>>                 model:  a Workspace
>>>                 paragraph:      a MultiNewParagraph
>>>                 markBlock:      a CharacterBlock with index 1 and
>>> character $( and rectangle
>>> 0@0 cor...etc...
>>>                 pointBlock:     a CharacterBlock with index 23 and
>>> rectangle 154@0 corner:
>>> 154@17
>>>  ...etc...
>>>                 beginTypeInIndex:       nil
>>>                 emphasisHere:   {a TextFontChange font: 1}
>>>                 lastParenLocation:      nil
>>>                 otherInterval:  (1 to: 22)
>>>                 oldInterval:    (1 to: 22)
>>>                 typeAhead:      a WriteStream ''
>>>                 styler:         nil
>>>
>>> SmalltalkEditor(TextEditor)>>dispatchOnKeyboardEvent:
>>>         Receiver: a SmalltalkEditor
>>>         Arguments and temporary variables:
>>>                 aKeyboardEvent:         [keystroke '<Cmd-d>']
>>>                 honorCommandKeys:       true
>>>                 openers:        nil
>>>                 closers:        nil
>>>                 result:         nil
>>>         Receiver's instance variables:
>>>                 morph:  a TextMorphForEditView(2114)
>>>                 selectionShowing:       false
>>>                 model:  a Workspace
>>>                 paragraph:      a MultiNewParagraph
>>>                 markBlock:      a CharacterBlock with index 1 and
>>> character $( and rectangle
>>> 0@0 cor...etc...
>>>                 pointBlock:     a CharacterBlock with index 23 and
>>> rectangle 154@0 corner:
>>> 154@17
>>>  ...etc...
>>>                 beginTypeInIndex:       nil
>>>                 emphasisHere:   {a TextFontChange font: 1}
>>>                 lastParenLocation:      nil
>>>                 otherInterval:  (1 to: 22)
>>>                 oldInterval:    (1 to: 22)
>>>                 typeAhead:      a WriteStream ''
>>>                 styler:         nil
>>>
>>> SmalltalkEditor(TextEditor)>>keyStroke:
>>>         Receiver: a SmalltalkEditor
>>>         Arguments and temporary variables:
>>>                 anEvent:        [keystroke '<Cmd-d>']
>>>         Receiver's instance variables:
>>>                 morph:  a TextMorphForEditView(2114)
>>>                 selectionShowing:       false
>>>                 model:  a Workspace
>>>                 paragraph:      a MultiNewParagraph
>>>                 markBlock:      a CharacterBlock with index 1 and
>>> character $( and rectangle
>>> 0@0 cor...etc...
>>>                 pointBlock:     a CharacterBlock with index 23 and
>>> rectangle 154@0 corner:
>>> 154@17
>>>  ...etc...
>>>                 beginTypeInIndex:       nil
>>>                 emphasisHere:   {a TextFontChange font: 1}
>>>                 lastParenLocation:      nil
>>>                 otherInterval:  (1 to: 22)
>>>                 oldInterval:    (1 to: 22)
>>>                 typeAhead:      a WriteStream ''
>>>                 styler:         nil
>>>
>>> [] in [] in TextMorphForEditView(TextMorph)>>keyStroke:
>>>         Receiver: a TextMorphForEditView(2114)
>>>         Arguments and temporary variables:
>>> <<error during printing>
>>>         Receiver's instance variables:
>>>                 bounds:         0@0 corner: 416@19
>>>                 owner:  a TransformMorph(1978)
>>>                 submorphs:      #()
>>>                 fullBounds:     0@0 corner: 416@19
>>>                 color:  Color black
>>>                 extension:      a MorphExtension (2184) [other:
>>>  (signalConnections -> a
>>> Dictionary(...etc...
>>>                 borderWidth:    0
>>>                 borderColor:    Color black
>>>                 textStyle:      a TextStyle Bitmap Envy Code R 10 regular
>>>                 text:   a Text for '(Morph>>#drawOn:) hash'
>>>                 wrapFlag:       true
>>>                 paragraph:      a MultiNewParagraph
>>>                 editor:         a SmalltalkEditor
>>>                 container:      nil
>>>                 predecessor:    nil
>>>                 successor:      nil
>>>                 backgroundColor:        nil
>>>                 margins:        nil
>>>                 editHistory:    nil
>>>                 editView:       a PluggableTextMorphPlus(3348)
>>>                 acceptOnCR:     false
>>>
>>> TextMorphForEditView(TextMorph)>>handleInteraction:fromEvent:
>>>         Receiver: a TextMorphForEditView(2114)
>>>         Arguments and temporary variables:
>>>                 interactionBlock:       [closure] in [] in
>>> TextMorphForEditView(TextMorph)>>keyStroke...etc...
>>>                 evt:    [keystroke '<Cmd-d>']
>>>                 oldEditor:      a SmalltalkEditor
>>>                 oldParagraph:   a MultiNewParagraph
>>>                 oldText:        a Text for '(Morph>>#drawOn:) hash'
>>>         Receiver's instance variables:
>>>                 bounds:         0@0 corner: 416@19
>>>                 owner:  a TransformMorph(1978)
>>>                 submorphs:      #()
>>>                 fullBounds:     0@0 corner: 416@19
>>>                 color:  Color black
>>>                 extension:      a MorphExtension (2184) [other:
>>>  (signalConnections -> a
>>> Dictionary(...etc...
>>>                 borderWidth:    0
>>>                 borderColor:    Color black
>>>                 textStyle:      a TextStyle Bitmap Envy Code R 10 regular
>>>                 text:   a Text for '(Morph>>#drawOn:) hash'
>>>                 wrapFlag:       true
>>>                 paragraph:      a MultiNewParagraph
>>>                 editor:         a SmalltalkEditor
>>>                 container:      nil
>>>                 predecessor:    nil
>>>                 successor:      nil
>>>                 backgroundColor:        nil
>>>                 margins:        nil
>>>                 editHistory:    nil
>>>                 editView:       a PluggableTextMorphPlus(3348)
>>>                 acceptOnCR:     false
>>>
>>> TextMorphForEditView>>handleInteraction:fromEvent:
>>>         Receiver: a TextMorphForEditView(2114)
>>>         Arguments and temporary variables:
>>>                 interActionBlock:       [closure] in [] in
>>> TextMorphForEditView(TextMorph)>>keyStroke...etc...
>>>                 evt:    [keystroke '<Cmd-d>']
>>>         Receiver's instance variables:
>>>                 bounds:         0@0 corner: 416@19
>>>                 owner:  a TransformMorph(1978)
>>>                 submorphs:      #()
>>>                 fullBounds:     0@0 corner: 416@19
>>>                 color:  Color black
>>>                 extension:      a MorphExtension (2184) [other:
>>>  (signalConnections -> a
>>> Dictionary(...etc...
>>>                 borderWidth:    0
>>>                 borderColor:    Color black
>>>                 textStyle:      a TextStyle Bitmap Envy Code R 10 regular
>>>                 text:   a Text for '(Morph>>#drawOn:) hash'
>>>                 wrapFlag:       true
>>>                 paragraph:      a MultiNewParagraph
>>>                 editor:         a SmalltalkEditor
>>>                 container:      nil
>>>                 predecessor:    nil
>>>                 successor:      nil
>>>                 backgroundColor:        nil
>>>                 margins:        nil
>>>                 editHistory:    nil
>>>                 editView:       a PluggableTextMorphPlus(3348)
>>>                 acceptOnCR:     false
>>>
>>> [] in TextMorphForEditView(TextMorph)>>keyStroke:
>>>         Receiver: a TextMorphForEditView(2114)
>>>         Arguments and temporary variables:
>>>                 evt:    [keystroke '<Cmd-d>']
>>>                 action:         nil
>>>         Receiver's instance variables:
>>>                 bounds:         0@0 corner: 416@19
>>>                 owner:  a TransformMorph(1978)
>>>                 submorphs:      #()
>>>                 fullBounds:     0@0 corner: 416@19
>>>                 color:  Color black
>>>                 extension:      a MorphExtension (2184) [other:
>>>  (signalConnections -> a
>>> Dictionary(...etc...
>>>                 borderWidth:    0
>>>                 borderColor:    Color black
>>>                 textStyle:      a TextStyle Bitmap Envy Code R 10 regular
>>>                 text:   a Text for '(Morph>>#drawOn:) hash'
>>>                 wrapFlag:       true
>>>                 paragraph:      a MultiNewParagraph
>>>                 editor:         a SmalltalkEditor
>>>                 container:      nil
>>>                 predecessor:    nil
>>>                 successor:      nil
>>>                 backgroundColor:        nil
>>>                 margins:        nil
>>>                 editHistory:    nil
>>>                 editView:       a PluggableTextMorphPlus(3348)
>>>                 acceptOnCR:     false
>>>
>>>
>>> --- The full stack ---
>>> CompiledMethod(Object)>>error:
>>> CompiledMethod(Object)>>errorSubscriptBounds:
>>> CompiledMethod(Object)>>basicAt:
>>> CompiledMethod class(ByteArray class)>>hashBytes:startingWith:
>>> CompiledMethod(ByteArray)>>hash
>>> UndefinedObject>>DoIt
>>> Compiler>>evaluate:in:to:notifying:ifFail:logged:
>>> [] in SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo:
>>> BlockClosure>>on:do:
>>> SmalltalkEditor(TextEditor)>>evaluateSelectionAndDo:
>>> SmalltalkEditor(TextEditor)>>evaluateSelection
>>> SmalltalkEditor(TextEditor)>>doIt
>>> SmalltalkEditor(TextEditor)>>doIt:
>>> SmalltalkEditor(TextEditor)>>dispatchOnKeyboardEvent:
>>> SmalltalkEditor(TextEditor)>>keyStroke:
>>> [] in [] in TextMorphForEditView(TextMorph)>>keyStroke:
>>> TextMorphForEditView(TextMorph)>>handleInteraction:fromEvent:
>>> TextMorphForEditView>>handleInteraction:fromEvent:
>>> [] in TextMorphForEditView(TextMorph)>>keyStroke:
>>>  - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
>>> ECToolSet class>>codeCompletionAround:textMorph:keyStroke:
>>> ToolSet class>>codeCompletionAround:textMorph:keyStroke:
>>> TextMorphForEditView(TextMorph)>>keyStroke:
>>> TextMorphForEditView>>keyStroke:
>>> TextMorphForEditView(TextMorph)>>handleKeystroke:
>>> KeyboardEvent>>sentTo:
>>> TextMorphForEditView(Morph)>>handleEvent:
>>> TextMorphForEditView(Morph)>>handleFocusEvent:
>>> [] in HandMorph>>sendFocusEvent:to:clear:
>>> BlockClosure>>on:do:
>>> PasteUpMorph>>becomeActiveDuring:
>>> HandMorph>>sendFocusEvent:to:clear:
>>> HandMorph>>sendEvent:focus:clear:
>>> HandMorph>>sendKeyboardEvent:
>>> HandMorph>>handleEvent:
>>> HandMorph>>processEvents
>>> [] in WorldState>>doOneCycleNowFor:
>>> Array(SequenceableCollection)>>do:
>>> WorldState>>handsDo:
>>> WorldState>>doOneCycleNowFor:
>>> WorldState>>doOneCycleFor:
>>> PasteUpMorph>>doOneCycle
>>> [] in Project class>>spawnNewProcess
>>> [] in BlockClosure>>newProcess
>>>
>>>
>>>
>>> --
>>> View this message in context:
>>> http://forum.world.st/CompiledMethod-hash-broken-on-CogVM-r2559-Win7-Squeak-4-3-tp4641061.html
>>> Sent from the Squeak - Dev mailing list archive at Nabble.com.
>>>
>>>
>>
>>
>> --
>> best,
>> Eliot
>>
>>
>>
>>
>>
>
>
> --
> Mariano
> http://marianopeck.wordpress.com
>
>


-- 
best,
Eliot

Reply via email to