[squeak-dev] The Trunk: Collections-ul.739.mcz

Clément Bera bera.clement at gmail.com
Wed Mar 1 16:04:38 UTC 2017


On Wed, Mar 1, 2017 at 12:45 AM, Eliot Miranda <eliot.miranda at gmail.com>
wrote:

> Hi Levente,
>
> On Tue, Feb 28, 2017 at 2:43 PM, Levente Uzonyi <leves at caesar.elte.hu>
> wrote:
>
>> Hi Eliot,
>>
>> I tried to change the selector in the special objects array, but it
>> didn't help. I get the same numbers as before.
>>
>> Here's what I did:
>> First, I changed #blockCopy to: #~~ in SmalltalkImage >>
>> #recreateSpecialObjectsArray.
>> Then, I evaluated the following snippet in a workspace:
>>
>> senders := SystemNavigation default allCallsOn: #~~.
>> Smalltalk recreateSpecialObjectsArray.
>> senders
>>          do: [ :methodReference |
>>                 | class |
>>                 class := methodReference actualClass.
>>                 class recompile: methodReference selector from: class ]
>>         displayingProgress: 'Recompiling...'.
>>
>> And finally I ran the benchmark.
>>
>> However, now #blockCopy: will just behave as #~~ should. And, it gives
>> the same number as #==. So, I suppose there are few other places to change
>> to get the right behavior (Compiler, Encoder, Whatever).
>>
>
> I forgot to tell you that you need to do
>     VariableNode initialize.  Decompiler initialize
> See variableNode class>>#initialize.  This fills StdSelectors, a class var
> of ParseNode, with the special selectors.  Sorry!
>
>
>> However, what's really interesting is how the JIT behaves in this case:
>> #== alone is about 1.43x slower than #== + #ifTrue:ifFalse: in this test.
>
>
> Yes, I chose to only inline when a comparison operator is followed by a
> conditional branch.  So any of #= #~= #== #~~ #> #< #>= #<= if used to
> compute a value will be compiled into a real send  That could be a
> mistake.  Let me know if you think it will be critical to performance.  The
> notion is that inlining the branch saves a lot (reifying the result,
> testing the result for being true, false or something else), but inlining
> just to obtain the result saves only the inline cached send overhead.  That
> could be the wrong call, but that's what I decided to do back in 2009.
>
>
Hi both,

I believe #== and #~~ are inlined even if they're not followed by a branch
in
#genIdenticalNoBranchArgIsConstant:rcvrIsConstant:argReg:rcvrReg:orNotIf:.
It's inlined to allow registers to stay live.

The other special selectors Eliot mentioned (#= #~= #> #< #>= #<=) are
however inlined only if followed by a branch.


>
>>
>> Levente
>>
>>
>> On Tue, 28 Feb 2017, Eliot Miranda wrote:
>>
>> Hi Levente,
>>> On Tue, Feb 28, 2017 at 10:44 AM, Levente Uzonyi <leves at caesar.elte.hu>
>>> wrote:
>>>       In case someone would like to defend the performance of #~~ and
>>> #notNil, here's a little benchmark I just wrote:
>>>
>>>       | base ifNilIfNotNil notIdentical notEqual notNil |
>>>       Smalltalk garbageCollect.
>>>       base := (1 to: 5) collect: [ :run |
>>>               [ 1 to: 100000000 do: [ :i | ] ] timeToRun ].
>>>
>>>       ifNilIfNotNil := (1 to: 5) collect: [ :run |
>>>               [ 1 to: 100000000 do: [ :i | i ifNil: [ false ] ifNotNil:
>>> [ true ] ] ] timeToRun ].
>>>
>>>       notIdentical := (1 to: 5) collect: [ :run |
>>>               [ 1 to: 100000000 do: [ :i | i ~~ nil ] ] timeToRun ].
>>>
>>>       notEqual := (1 to: 5) collect: [ :run |
>>>               [ 1 to: 100000000 do: [ :i | i ~= nil ] ] timeToRun ].
>>>
>>>
>>>       notNil := (1 to: 5) collect: [ :run |
>>>               [ 1 to: 100000000 do: [ :i | i notNil ] ] timeToRun ].
>>>
>>>       {
>>>               #ifNilIfNotNil -> ifNilIfNotNil.
>>>               #notIdentical -> notIdentical.
>>>               #notEqual -> notEqual.
>>>               #notNil -> notNil
>>>       }
>>>               replace: [ :each |
>>>                       each key -> (each value average - base average)
>>> asFloat ];
>>>               sort: #value ascending
>>>
>>>       "{#ifNilIfNotNil->73.6 . #notNil->336.8 . #notIdentical->511.6 .
>>> #notEqual->3354.0}"
>>>
>>>       So it's 4.5x faster than #notNil and 7x faster than #~~ on 64-bit
>>> Spur on Linux. Once we have jitted #~~, I'll change the code again.
>>>
>>>
>>> IIRC, all one needs to get jitted #~~ is to store #~~ in place of
>>> blockCopy: in the specialSelectors array and recompile all senders of #~~.
>>> You may need to collect all senders of #~~ before you make the
>>> swap since putting it in the specialSelectors array may confuse
>>> allReferencesTo: et al.
>>>
>>>       Levente
>>>
>>>
>>>       On Tue, 28 Feb 2017, commits at source.squeak.org wrote:
>>>
>>>             Levente Uzonyi uploaded a new version of Collections to
>>> project The Trunk:
>>>             http://source.squeak.org/trunk/Collections-ul.739.mcz
>>>
>>>             ==================== Summary ====================
>>>
>>>             Name: Collections-ul.739
>>>             Author: ul
>>>             Time: 28 February 2017, 7:34:55.711173 pm
>>>             UUID: 66c6ecf2-71bf-4e7d-80e6-5ace72fa19ba
>>>             Ancestors: Collections-ul.738
>>>
>>>             - use micro optimization for #~~ and #notNil in common
>>> collection methods
>>>             - reuse one of the OrderedCollections in RunArray >>
>>> #scanFrom:
>>>             - two other minor tweaks in KeyedSet
>>>             - removed accidentally commited Set >> #includes2:
>>>
>>>             =============== Diff against Collections-ul.738
>>> ===============
>>>
>>>             Item was changed:
>>>              ----- Method: Dictionary>>includesKey: (in category
>>> 'testing') -----
>>>              includesKey: key
>>>                     "Answer whether the receiver has a key equal to the
>>> argument, key."
>>>
>>>             +       (array at: (self scanFor: key)) ifNil: [ ^false ]
>>> ifNotNil: [ ^true ]!
>>>             -        ^(array at: (self scanFor: key)) notNil!
>>>
>>>             Item was changed:
>>>              ----- Method: KeyedSet>>includesKey: (in category
>>> 'testing') -----
>>>              includesKey: key
>>>
>>>             +       (array at: (self scanFor: key)) ifNil: [ ^false ]
>>> ifNotNil: [ ^true ]!
>>>             -       ^ (array at: (self scanFor: key)) notNil!
>>>
>>>             Item was changed:
>>>              ----- Method: KeyedSet>>remove:ifAbsent: (in category
>>> 'removing') -----
>>>              remove: oldObject ifAbsent: aBlock
>>>
>>>                     | index |
>>>                     index := self scanFor: (keyBlock value: oldObject).
>>>             +       (array at: index) ifNil: [ ^ aBlock value ].
>>>             -       (array at: index) == nil ifTrue: [ ^ aBlock value ].
>>>                     array at: index put: nil.
>>>                     tally := tally - 1.
>>>                     self fixCollisionsFrom: index.
>>>                     ^ oldObject!
>>>
>>>             Item was changed:
>>>              ----- Method: KeyedSet>>removeKey:ifAbsent: (in category
>>> 'removing') -----
>>>              removeKey: key ifAbsent: aBlock
>>>
>>>                     | index obj |
>>>                     index := self scanFor: key.
>>>             +       obj := (array at: index) ifNil: [ ^ aBlock value ].
>>>             -       (obj := array at: index) == nil ifTrue: [ ^ aBlock
>>> value ].
>>>                     array at: index put: nil.
>>>                     tally := tally - 1.
>>>                     self fixCollisionsFrom: index.
>>>                     ^ obj enclosedSetElement!
>>>
>>>             Item was changed:
>>>              ----- Method: RunArray class>>scanFrom: (in category
>>> 'instance creation') -----
>>>              scanFrom: strm
>>>                     "Read the style section of a fileOut or sources
>>> file.  nextChunk has already been done.  We need to return a RunArray of
>>> TextAttributes of various kinds.  These are written by
>>>             the implementors of writeScanOn:"
>>>                     | runs values attrList char |
>>>                     (strm peekFor: $( ) ifFalse: [^ nil].
>>>                     runs := OrderedCollection new.
>>>                     [strm skipSeparators.
>>>                      strm peekFor: $)] whileFalse:
>>>                             [runs add: (Number readFrom: strm)].
>>>                     values := OrderedCollection new.        "Value array"
>>>                     attrList := OrderedCollection new.      "Attributes
>>> list"
>>>                     [(char := strm peek) == nil] whileFalse: [
>>>                             (char isSeparator or: [ char = $!! ])
>>>                                     ifTrue: [ "n.b. Skip $!! to meet
>>> expectations of RunArrayTest>>testScanFromTrailer.
>>>                                                     The example string
>>> used in that test does not seem to match the implemention
>>>                                                     of the fileOut
>>> serialization, but the test may be right and the implementation
>>>                                                     wrong. In any case,
>>> relax the parsing here to meet the test expectations, and to
>>>                                                     be more consistent
>>> with the original version of this method that assumed any
>>>                                                     unexpected charater
>>> to be a separator. -dtl Jan 2014"
>>>                                             strm next "space, cr do
>>> nothing"]
>>>                                     ifFalse: [char == $,
>>>                                                     ifTrue: [strm next.
>>>                                                             values add:
>>> attrList asArray.
>>>             +                                               attrList
>>> reset ]
>>>             -                                               attrList :=
>>> OrderedCollection new]
>>>                                                     ifFalse: [attrList
>>> add:  (TextAttribute newFrom: strm)]
>>>                                             ]
>>>                             ].
>>>                     values add: attrList asArray.
>>>                     ^ self runs: runs asArray values: (values copyFrom:
>>> 1 to: runs size) asArray
>>>              "
>>>              RunArray scanFrom: (ReadStream on: '(14 50
>>> 312)f1,f1b,f1LInteger +;i')
>>>              "!
>>>
>>>             Item was removed:
>>>             - ----- Method: Set>>includes2: (in category 'testing') -----
>>>             - includes2: anObject - -       ^((array at: (self scanFor:
>>> anObject)) == nil) not!
>>>
>>>             Item was changed:
>>>              ----- Method: WeakIdentityDictionary>>includesKey: (in
>>> category 'testing') -----
>>>              includesKey: key
>>>                     "Answer whether the receiver has a key equal to the
>>> argument, key."
>>>
>>>             +       (array at: (self scanFor: key))
>>>             +               ifNil: [
>>>             +                       "it just has been reclaimed"
>>>             +                       ^false]
>>>             +               ifNotNil: [ :element |
>>>             +                       element == vacuum
>>>             +                               ifTrue: [ ^false ]
>>>             +                               ifFalse: [ ^true ] ]!
>>>             -       ^(array at: (self scanFor: key))
>>>             -               ifNil:
>>>             -                       ["it just has been reclaimed"
>>>             -                       false]
>>>             -               ifNotNil: [:element | element ~~ vacuum]!
>>>
>>>             Item was changed:
>>>              ----- Method: WeakSet>>includes: (in category 'testing')
>>> -----
>>>              includes: anObject
>>>
>>>                     (array at: (self scanFor: anObject))
>>>                             ifNil: [ ^false ]
>>>             +               ifNotNil: [ :object |
>>>             +                       object == flag
>>>             +                               ifTrue: [ ^false ]
>>>             +                               ifFalse: [ ^true ] ]!
>>>             -               ifNotNil: [ :object | ^object ~~ flag ]!
>>>
>>>
>>>
>>>
>>>
>>> --
>>> _,,,^..^,,,_
>>> best, Eliot
>>>
>>>
>>
>>
>>
>
>
> --
> _,,,^..^,,,_
> best, Eliot
>
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20170301/be5ba2ac/attachment.html>


More information about the Squeak-dev mailing list