On 8 March 2013 15:58, Sven Van Caekenberghe <[email protected]> wrote:
> Thanks.
>
> But my 2nd and 3rd runs crashed, both at
>
> Smalltalk stack dump:
> 0xbf9c4c18 M MethodDictionary(Object)>becomeForward: 0x79299080: a(n)
> MethodDictionary
> 0xbf9c4c44 M MethodDictionary>grow 0x79299080: a(n) MethodDictionary
> 0xbf9c4c5c M MethodDictionary(HashedCollection)>fullCheck 0x79299080: a(n)
> MethodDictionary
> 0xbf9c4c78 M MethodDictionary>at:put: 0x79299080: a(n) MethodDictionary
>
> so it is still becomeForward: but while growing a MethodDictionary, which is
> a pretty basic operation I guess.
>
this is one more explanation why things so slow when you installing new stuff
because when you just recompiling existing methods, all methods are
going into very same dictionary and
it never grows..
but imagine that you creating a fresh class, and then one by one ,
adding new methods to it
(and having like 100 methods per class)
a default capacity for method dictionary is 24 methods:
new
"Create a new instance with 32 slots, which can hold at most 24
methods before growing is necessary."
^self newForCapacity: 32
so , if your classes have more, it will grow and use become.. trashing
the performace :)
btw, i wonder why MethodDictionary is variable sized..
it could hold keys and values as pairs in its array slot, without need
to do #become on grow (just replacing array with new one)...
> On 08 Mar 2013, at 15:46, Esteban Lorenzano <[email protected]> wrote:
>
>> included :)
>>
>> On Mar 8, 2013, at 2:52 PM, Sven Van Caekenberghe <[email protected]> wrote:
>>
>>> Hi Esteban,
>>>
>>> On 08 Mar 2013, at 12:44, Esteban Lorenzano <[email protected]> wrote:
>>>
>>>> Hi Sven,
>>>>
>>>> One of the problems we currently have is that all method installation
>>>> execute a becomeForward:, which is of course not terrible cleaver... I
>>>> tried using the squeak implementation of it and everything looks working
>>>> (and it has a small optimization that can help).
>>>>
>>>> Can you trying the load by installing it?
>>>>
>>>> CompiledMethod>>#setSourcePointer: srcPointer
>>>> "We can't change the trailer of existing method, since it could have a
>>>> completely different format. Therefore we need to generate a copy
>>>> with new trailer, containing a srcPointer, and then #become it."
>>>> | trailer copy start |
>>>>
>>>> trailer := srcPointer = 0
>>>> ifTrue: [
>>>> "catch the common case of setting the source pointer
>>>> to 0 when already 0"
>>>> self sourcePointer = 0 ifTrue: [ ^ self ].
>>>> CompiledMethodTrailer empty ]
>>>> ifFalse: [
>>>> CompiledMethodTrailer new sourcePointer: srcPointer ].
>>>> copy := self copyWithTrailerBytes: trailer.
>>>>
>>>> "ar 3/31/2010: Be a bit more clever since #become: is slow.
>>>> If the old and the new trailer have the same size, just replace it."
>>>> (self trailer class == trailer class and:[ self size = copy size ])
>>>> ifTrue: [
>>>> start := self endPC + 1.
>>>> self replaceFrom: start to: self size with: copy
>>>> startingAt: start ]
>>>> ifFalse: [
>>>> self becomeForward: copy ].
>>>>
>>>> ^self "will be copy if #become was needed"
>>>>
>>>> this can help in the speed and also can help on the vm crash problem (even
>>>> if it is a workaround)...
>>>>
>>>> Esteban
>>>
>>> I used the following version
>>>
>>> CompiledMethod>>#setSourcePointer: srcPointer
>>> "We can't change the trailer of existing method, since it could have
>>> completely different format.
>>> Therefore we need to generate a copy with new trailer, containing
>>> scrPointer, and then become it."
>>>
>>> | trailer copy |
>>> trailer := CompiledMethodTrailer new sourcePointer: srcPointer.
>>> copy := self copyWithTrailerBytes: trailer.
>>> "If possible do a replace in place as an optimization"
>>> (self trailer class == trailer class and: [ self size = copy size ])
>>> ifTrue: [
>>> | start |
>>> start := self endPC + 1.
>>> self replaceFrom: start to: self size with: copy
>>> startingAt: start ]
>>> ifFalse: [ self becomeForward: copy ].
>>> ^ self
>>>
>>> And it worked fine. My build completed successfully (1 try only).
>>> But it took about as long as before (10 minutes using a Cog based VM).
>>>
>>> Thanks again for the suggestion, I think we should incorporate that change,
>>> no ?
>>>
>>> The class test is ugly and most probably not necessary in the current
>>> image, I would say.
>>>
>>> Sven
>>>
>>>> On Mar 8, 2013, at 11:53 AM, Sven Van Caekenberghe <[email protected]> wrote:
>>>>
>>>>>
>>>>> On 08 Mar 2013, at 11:16, Sven Van Caekenberghe <[email protected]> wrote:
>>>>>
>>>>>> But I have said this before: the wall clock time of loading a lot of
>>>>>> code is actually close to unacceptable - I don't think it is the
>>>>>> download or the compilation, but more all the dynamic stuff that happens
>>>>>> after that. There should be a way to not do all those updates for each
>>>>>> method and move the updates to one big batch update after the load - if
>>>>>> that is possible.
>>>>>
>>>>> To continue my rant (sorry ;-) about the problem with slow code loading.
>>>>>
>>>>> These are some benchmarks on the same machine:
>>>>>
>>>>> $ ./vm.sh experimental.image eval '[Smalltalk allClassesAndTraits do:
>>>>> #compileAll] timeToRun'
>>>>> 106532
>>>>>
>>>>> $ ./stack/vm.sh experimental.image eval '[Smalltalk allClassesAndTraits
>>>>> do: #compileAll] timeToRun'
>>>>> 221708
>>>>>
>>>>> So it takes like 3 minutes to recompile every method in the system.
>>>>>
>>>>> How in the hell can it take 40 minutes to load some code (with all
>>>>> packages already present in the package-cache (but then again the
>>>>> package-cache is only 3.5 Mb, which could be downloaded in seconds)) ?
>>>>>
>>>>> Sven
>>>>>
>>>>> --
>>>>> Sven Van Caekenberghe
>>>>> http://stfx.eu
>>>>> Smalltalk is the Red Pill
>>>>>
>>>>>
>>>>
>>>>
>>>
>>>
>>
>>
>
>
--
Best regards,
Igor Stasenko.