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