Hashed collection improvements: Some code

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
16 messages Options
Reply | Threaded
Open this post in threaded view
|

Hashed collection improvements: Some code

Martin McClure-2
OK, here's a filein that improves Pharo hashed collection performance
quite a bit. Large collections are much faster, and small ones are
pretty much the same speed as before. There are basically two fairly
simple changes; the basic structure and algorithms of the collections is
unchanged. The changes:

1. Spread identity hash values.
2. Make table sizes prime.


File it into PharoCore-1.0-10491rc1.image. It'll take a minute or two
since it has to rehash the world halfway through. I don't know how to
make another kind of packaging that can do that, so I'll leave that to
someone else.

After the filein, there are some test failures, most of which do not
seem to be *directly* related. I'm hoping someone that knows the
affected tests can take a look and comment:


Unexpectedly pass ObjectFinalizerTests>>#testFinalizationOfEquals
   Not clear why, but this does not seem to be a problem :-)

Fails HostWindowTests>>#testOne
   But this test fails in the core image on Linux; HostWindows do not
   seem to be implemented for Linux.

Error on FontTest>>#testMultistringFont
   Japanese StrikeFonts have nil characterToGlyphMap,
   #createCharacterToGlyphMap answers nil,
   not immediately clear how this is supposed to be initialized for fonts
   with codepoints > 255.

PackageInfoTest>>testKernelPackage
   because some method in kernel package for Object is not in Object.
   I've changed #hash, so that's probably it.

Regards,

-Martin

'From Pharo1.0rc1 of 19 October 2009 [Latest update: #10491] on 23 October 2009 at 5:54:55 pm'!

!ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009 22:30'!
identityHashTEMP
        "Answer a SmallInteger whose value is related to the receiver's identity.
        This method must not be overridden, except by SmallInteger.
        Primitive. Fails if the receiver is a SmallInteger. Essential.
        See Object documentation whatIsAPrimitive.

        Do not override."

        ^self primIdentityHash bitShift: 18! !


!Object methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009 22:46'!
hashTEMP
        "Answer a SmallInteger whose value is related to the receiver's identity.
        May be overridden, and should be overridden in any classes that define = "

        ^ self primIdentityHash bitShift: 18! !


!ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009 21:13'!
primIdentityHash
        "Answer a SmallInteger whose value is related to the receiver's identity.
        This method must not be overridden, except by SmallInteger.
        Primitive. Fails if the receiver is a SmallInteger. Essential.
        See Object documentation whatIsAPrimitive.

        Do not override."

        <primitive: 75>
        self primitiveFailed! !


!SmallInteger methodsFor: 'comparing' stamp: 'MartinMcClure 10/23/2009 17:53'!
primIdentityHash
        "Senders of primIdentityHash do it because they expect to get an answer from 1-4095.
        So they should not send this to SmallIntegers, but should use #identityHash"
       
        "^self shouldNotImplement"
       
        "...OK, only here for the sake of FixedIdentitySet, which may not need it since it is probably not used for Integers.
        And FixedIdentitySet itself may not be needed now that IdentitySets are faster."
       
        ^self! !


!IdentityDictionary methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 14:55'!
scanFor: anObject
        "Scan the key array for the first slot containing either a nil (indicating an empty slot) or an element that matches anObject. Answer the index of that slot or zero if no slot is found. This method will be overridden in various subclasses that have different interpretations for matching elements."
        | finish hash start element |
        finish := array size.
        start := (anObject identityHash \\ finish) + 1.

        "Search from (hash mod size) to the end."
        start to: finish do:
                [:index | ((element := array at: index) == nil or: [element key == anObject])
                        ifTrue: [^ index ]].

        "Search from 1 to where we started."
        1 to: start-1 do:
                [:index | ((element := array at: index) == nil or: [element key == anObject])
                        ifTrue: [^ index ]].

        ^ 0  "No match AND no empty slot"! !


!IdentitySet methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 14:57'!
scanFor: anObject
        "Scan the key array for the first slot containing either a nil (indicating an empty slot) or an element that matches anObject. Answer the index of that slot or zero if no slot is found. This method will be overridden in various subclasses that have different interpretations for matching elements."
        | finish hash start element |
        finish := array size.
        start := (anObject identityHash \\ finish) + 1.

        "Search from (hash mod size) to the end."
        start to: finish do:
                [:index | ((element := array at: index) == nil or: [element == anObject])
                        ifTrue: [^ index ]].

        "Search from 1 to where we started."
        1 to: start-1 do:
                [:index | ((element := array at: index) == nil or: [element == anObject])
                        ifTrue: [^ index ]].

        ^ 0  "No match AND no empty slot"! !


!MethodDictionary methodsFor: 'private' stamp: 'MartinMcClure 10/22/2009 21:24'!
scanFor: anObject
        "Scan the key array for the first slot containing either a nil (indicating an empty slot) or an element that matches anObject. Answer the index of that slot or zero if no slot is found. This method will be overridden in various subclasses that have different interpretations for matching elements."
        | element start finish |
        finish := array size.
        start := (anObject primIdentityHash \\ finish) + 1.

        "Search from (hash mod size) to the end."
        start to: finish do:
                [:index | ((element := self basicAt: index) == nil or: [element == anObject])
                        ifTrue: [^ index ]].

        "Search from 1 to where we started."
        1 to: start-1 do:
                [:index | ((element := self basicAt: index) == nil or: [element == anObject])
                        ifTrue: [^ index ]].

        ^ 0  "No match AND no empty slot"! !


!WeakIdentityKeyDictionary methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 14:54'!
scanFor: anObject
        "ar 10/21/2000: The method has been copied to this location to indicate that whenever #scanFor: changes #scanForNil: must be changed in the receiver as well."
        "Scan the key array for the first slot containing either a nil (indicating an empty slot) or an element that matches anObject. Answer the index of that slot or zero if no slot is found. This method will be overridden in various subclasses that have different interpretations for matching elements."
        | element start finish hash |
        finish := array size.
        start := (anObject identityHash \\ finish) + 1.

        "Search from (hash mod size) to the end."
        start to: finish do:
                [:index | ((element := array at: index) == nil or: [element key == anObject])
                        ifTrue: [^ index ]].

        "Search from 1 to where we started."
        1 to: start-1 do:
                [:index | ((element := array at: index) == nil or: [element key == anObject])
                        ifTrue: [^ index ]].

        ^ 0  "No match AND no empty slot"! !

!WeakIdentityKeyDictionary methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 14:54'!
scanForNil: anObject
        "Private. Scan the key array for the first slot containing nil (indicating an empty slot). Answer the index of that slot."
        | start finish hash |
        finish := array size.
        start := (anObject identityHash \\ array size) + 1.

        "Search from (hash mod size) to the end."
        start to: finish do:
                [:index | (array at: index) == nil ifTrue: [^ index ]].

        "Search from 1 to where we started."
        1 to: start-1 do:
                [:index | (array at: index) == nil ifTrue: [^ index ]].

        ^ 0  "No match AND no empty slot"! !







"---------------------Do surgery and rehash before continuing--------------------------"!

| dict method |
dict := ProtoObject methodDictionary.
method := dict at: #identityHashTEMP.
dict at: #identityHash put: method.
dict := Object methodDictionary.
method := dict at: #hashTEMP.
dict at: #identityHash put: method.

Set rehashAllSets.!

"---------- Life should be... better now :-) -----------------------------"!



!ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009 22:30'!
identityHash
        "Answer a SmallInteger whose value is related to the receiver's identity.
        This method must not be overridden, except by SmallInteger.
        Primitive. Fails if the receiver is a SmallInteger. Essential.
        See Object documentation whatIsAPrimitive.

        Do not override."

        ^self primIdentityHash bitShift: 18! !


!Object methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009 22:46'!
hash
        "Answer a SmallInteger whose value is related to the receiver's identity.
        May be overridden, and should be overridden in any classes that define = "

        ^ self primIdentityHash bitShift: 18! !


!FixedIdentitySet methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 14:49'!
indexOf: anObject
        anObject isNil ifTrue: [self error: 'This class collection cannot handle nil as an element'].
        ^ (anObject primIdentityHash bitAnd: self basicSize - 1) + 1! !


!Set class methodsFor: 'sizing' stamp: 'MartinMcClure 10/23/2009 09:44'!
goodPrimes
        "Answer a sorted array of prime numbers less than one hundred million
        that make good hash table sizes. Should be expanded to more numbers if folks
        want to make larger collections.
        Need to check with Andres' book when I get back to work to see if I remembered
        it right :-)
       
        Generated with this code:
       
        | prevPrime primes goodPrimes |
        goodPrimes := OrderedCollection new.
        primes := Integer largePrimesUpTo: 100000000.
        goodPrimes add: 5.
        prevPrime := 5.
        primes do:
                [:prime | prime > (prevPrime * 4 // 3) ifTrue:
                        [| lowByte | lowByte := prime bitAnd: 16rFF.
                        (lowByte > 10 and: [lowByte < 245]) ifTrue:
                                [goodPrimes add: prime.
                                prevPrime := prime]]].
        ^goodPrimes asArray printString"
       
        ^#(5 11 17 23 31 43 59 79 107 149 199 269 359 479 641 857 1151 1549 2069 2767 3691 4931 6577 8779 11717 15629 20849 27799 37087 49451 65951 87943 117259 156347 208463 277961 370619 494167 658897 878539 1171393 1561883 2082527 2776727 3702313 4936423 6581909 8775947 11701267 15601723 20802317 27736427 36981911 49309219 65745677 87660917)!
]style[(10 311 405 337)f2b,f2,f1,f2! !

!Set class methodsFor: 'sizing' stamp: 'MartinMcClure 10/23/2009 10:14'!
goodPrimeAtLeast: lowerLimit
        "Answer the next good prime >= lowerlimit.
        If lowerLimit is larger than the largest known good prime,
        just make it odd."
       
        | primes low mid high prime |
        primes := self goodPrimes.
        low := 1.
        high := primes size.
        lowerLimit > (primes at: high) ifTrue:
                [^lowerLimit even
                        ifTrue: [lowerLimit + 1]
                        ifFalse: [lowerLimit]].
        [mid := high - low // 2 + low.
                prime := primes at: mid.
                prime < lowerLimit
                        ifTrue: [low := mid]
                        ifFalse: [high := mid].
                high - low <= 1 ifTrue:
                        [^primes at: high].
                prime == lowerLimit ifTrue:
                        [^prime]] repeat
               
        !
]style[(28 158 411)f2b,f2,f1! !

!Set methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 10:25'!
growSize
        "Answer what my next higher table size should be"
        ^ self class goodPrimeAtLeast: array size * 2! !


!Set methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 10:25'!
grow
        "Grow the elements array and reinsert the old elements"
        | oldElements |
        oldElements := array.
        array := Array new: self growSize.
        tally := 0.
        oldElements do:
                [:each | each == nil ifFalse: [self noCheckAdd: each]]! !


!Set class methodsFor: 'instance creation' stamp: 'MartinMcClure 10/23/2009 10:19'!
sizeFor: nElements
        "Large enough size to hold nElements with some slop (see fullCheck)"
        nElements <= 0 ifTrue: [^ 5].
        ^ self goodPrimeAtLeast: (nElements+1*4//3)! !



!WeakSet methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 10:26'!
grow
        "Grow the elements array if needed.
        Since WeakSets just nil their slots, alot of the occupied (in the eyes of the set) slots are usually empty. Doubling size if unneeded can lead to BAD performance, therefore we see if reassigning the <live> elements to a Set of similiar size leads to a sufficiently (50% used here) empty set first.
        and reinsert the old elements"
        |oldTally|
        oldTally := tally.
        self growTo: array size.
        oldTally >> 1 < tally ifTrue: [
        self growTo: self growSize]! !


!MethodPragmaTest methodsFor: 'testing-primitives' stamp: 'MartinMcClure 10/23/2009 12:37'!
testPrimitiveIndexed2
        "This test useses the #identityHash primitive."

        self compile: '<primitive: 75> ^ #idHash' selector: #idHash.
        self assert: self idHash = self primIdentityHash.! !


!SmallInteger reorganize!
('arithmetic' * + - / // \\ gcd: quo:)
('bit manipulation' bitAnd: bitOr: bitShift: bitXor: hashMultiply highBit highBitOfMagnitude lowBit)
('comparing' < <= = > >= hash identityHash primIdentityHash ~=)
('converting' as31BitSmallInt asFloat)
('copying' clone deepCopy shallowCopy veryDeepCopyWith:)
('printing' decimalDigitLength destinationBuffer: numberOfDigitsInBase: printOn:base: printOn:base:nDigits: printString printStringBase: printStringBase:nDigits: threeDigitName)
('system primitives' asOop digitAt: digitAt:put: digitLength instVarAt: nextInstance nextObject)
('testing' even isLarge odd)
('private' fromString:radix: highBitOfPositiveReceiver)
!


!Set class reorganize!
('initialization' quickRehashAllSets rehashAllSets)
('sizing' goodPrimeAtLeast: goodPrimes)
('instance creation' new new: newFrom: sizeFor:)
!

ProtoObject removeSelector: #identityHashTEMP!
Object removeSelector: #hashTEMP!

!ProtoObject reorganize!
('apply primitives' tryNamedPrimitive tryNamedPrimitive: tryNamedPrimitive:with: tryNamedPrimitive:with:with: tryNamedPrimitive:with:with:with: tryNamedPrimitive:with:with:with:with: tryNamedPrimitive:with:with:with:with:with: tryNamedPrimitive:with:with:with:with:with:with: tryNamedPrimitive:with:with:with:with:with:with:with: tryPrimitive:withArgs:)
('closure-prims' privGetInstVar: privRemoteReturnTo: privSetInHolder: privSetInstVar:put: privStoreIn:instVar:)
('comparing' == identityHash primIdentityHash ~~)
('debugging' doOnlyOnce: flag: rearmOneShot withArgs:executeMethod:)
('initialize-release' initialize)
('method execution' executeMethod: with:executeMethod: with:with:executeMethod: with:with:with:executeMethod: with:with:with:with:executeMethod:)
('objects from disk' rehash)
('system primitives' become: cannotInterpret: doesNotUnderstand: nextInstance nextObject)
('testing' ifNil: ifNil:ifNotNil: ifNotNil: ifNotNil:ifNil: isInMemory isNil pointsTo:)
!


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Andres Valloud-4
Wonderful!  I think I can contribute a different kind of brain surgery,
I'll try to hack that together in a bit.

Martin McClure wrote:

> OK, here's a filein that improves Pharo hashed collection performance
> quite a bit. Large collections are much faster, and small ones are
> pretty much the same speed as before. There are basically two fairly
> simple changes; the basic structure and algorithms of the collections is
> unchanged. The changes:
>
> 1. Spread identity hash values.
> 2. Make table sizes prime.
>
>
> File it into PharoCore-1.0-10491rc1.image. It'll take a minute or two
> since it has to rehash the world halfway through. I don't know how to
> make another kind of packaging that can do that, so I'll leave that to
> someone else.
>
> After the filein, there are some test failures, most of which do not
> seem to be *directly* related. I'm hoping someone that knows the
> affected tests can take a look and comment:
>
>
> Unexpectedly pass ObjectFinalizerTests>>#testFinalizationOfEquals
>    Not clear why, but this does not seem to be a problem :-)
>
> Fails HostWindowTests>>#testOne
>    But this test fails in the core image on Linux; HostWindows do not
>    seem to be implemented for Linux.
>
> Error on FontTest>>#testMultistringFont
>    Japanese StrikeFonts have nil characterToGlyphMap,
>    #createCharacterToGlyphMap answers nil,
>    not immediately clear how this is supposed to be initialized for fonts
>    with codepoints > 255.
>
> PackageInfoTest>>testKernelPackage
>    because some method in kernel package for Object is not in Object.
>    I've changed #hash, so that's probably it.
>
> Regards,
>
> -Martin
>  

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Stéphane Ducasse
In reply to this post by Martin McClure-2
Martin

are these changes related to the graphs you sent?
I will have a look after my hospital check.
Andres? Nicolas?
Any feedback?
Martin I imagine that I can package the changes :)


Stef

On Oct 24, 2009, at 4:01 AM, Martin McClure wrote:

> OK, here's a filein that improves Pharo hashed collection  
> performance quite a bit. Large collections are much faster, and  
> small ones are pretty much the same speed as before. There are  
> basically two fairly simple changes; the basic structure and  
> algorithms of the collections is unchanged. The changes:
>
> 1. Spread identity hash values.
> 2. Make table sizes prime.
>
>
> File it into PharoCore-1.0-10491rc1.image. It'll take a minute or  
> two since it has to rehash the world halfway through. I don't know  
> how to make another kind of packaging that can do that, so I'll  
> leave that to someone else.
>
> After the filein, there are some test failures, most of which do not  
> seem to be *directly* related. I'm hoping someone that knows the  
> affected tests can take a look and comment:
>
>
> Unexpectedly pass ObjectFinalizerTests>>#testFinalizationOfEquals
>  Not clear why, but this does not seem to be a problem :-)
>
> Fails HostWindowTests>>#testOne
>  But this test fails in the core image on Linux; HostWindows do not
>  seem to be implemented for Linux.
>
> Error on FontTest>>#testMultistringFont
>  Japanese StrikeFonts have nil characterToGlyphMap,
>  #createCharacterToGlyphMap answers nil,
>  not immediately clear how this is supposed to be initialized for  
> fonts
>  with codepoints > 255.
>
> PackageInfoTest>>testKernelPackage
>  because some method in kernel package for Object is not in Object.
>  I've changed #hash, so that's probably it.
>
> Regards,
>
> -Martin
> 'From Pharo1.0rc1 of 19 October 2009 [Latest update: #10491] on 23  
> October 2009 at 5:54:55 pm'!
>
> !ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure  
> 10/22/2009 22:30'!
> identityHashTEMP
> "Answer a SmallInteger whose value is related to the receiver's  
> identity.
> This method must not be overridden, except by SmallInteger.
> Primitive. Fails if the receiver is a SmallInteger. Essential.
> See Object documentation whatIsAPrimitive.
>
> Do not override."
>
> ^self primIdentityHash bitShift: 18! !
>
>
> !Object methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009  
> 22:46'!
> hashTEMP
> "Answer a SmallInteger whose value is related to the receiver's  
> identity.
> May be overridden, and should be overridden in any classes that  
> define = "
>
> ^ self primIdentityHash bitShift: 18! !
>
>
> !ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure  
> 10/22/2009 21:13'!
> primIdentityHash
> "Answer a SmallInteger whose value is related to the receiver's  
> identity.
> This method must not be overridden, except by SmallInteger.
> Primitive. Fails if the receiver is a SmallInteger. Essential.
> See Object documentation whatIsAPrimitive.
>
> Do not override."
>
> <primitive: 75>
> self primitiveFailed! !
>
>
> !SmallInteger methodsFor: 'comparing' stamp: 'MartinMcClure  
> 10/23/2009 17:53'!
> primIdentityHash
> "Senders of primIdentityHash do it because they expect to get an  
> answer from 1-4095.
> So they should not send this to SmallIntegers, but should use  
> #identityHash"
>
> "^self shouldNotImplement"
>
> "...OK, only here for the sake of FixedIdentitySet, which may not  
> need it since it is probably not used for Integers.
> And FixedIdentitySet itself may not be needed now that IdentitySets  
> are faster."
>
> ^self! !
>
>
> !IdentityDictionary methodsFor: 'private' stamp: 'MartinMcClure  
> 10/23/2009 14:55'!
> scanFor: anObject
> "Scan the key array for the first slot containing either a nil  
> (indicating an empty slot) or an element that matches anObject.  
> Answer the index of that slot or zero if no slot is found. This  
> method will be overridden in various subclasses that have different  
> interpretations for matching elements."
> | finish hash start element |
> finish := array size.
> start := (anObject identityHash \\ finish) + 1.
>
> "Search from (hash mod size) to the end."
> start to: finish do:
> [:index | ((element := array at: index) == nil or: [element key ==  
> anObject])
> ifTrue: [^ index ]].
>
> "Search from 1 to where we started."
> 1 to: start-1 do:
> [:index | ((element := array at: index) == nil or: [element key ==  
> anObject])
> ifTrue: [^ index ]].
>
> ^ 0  "No match AND no empty slot"! !
>
>
> !IdentitySet methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009  
> 14:57'!
> scanFor: anObject
> "Scan the key array for the first slot containing either a nil  
> (indicating an empty slot) or an element that matches anObject.  
> Answer the index of that slot or zero if no slot is found. This  
> method will be overridden in various subclasses that have different  
> interpretations for matching elements."
> | finish hash start element |
> finish := array size.
> start := (anObject identityHash \\ finish) + 1.
>
> "Search from (hash mod size) to the end."
> start to: finish do:
> [:index | ((element := array at: index) == nil or: [element ==  
> anObject])
> ifTrue: [^ index ]].
>
> "Search from 1 to where we started."
> 1 to: start-1 do:
> [:index | ((element := array at: index) == nil or: [element ==  
> anObject])
> ifTrue: [^ index ]].
>
> ^ 0  "No match AND no empty slot"! !
>
>
> !MethodDictionary methodsFor: 'private' stamp: 'MartinMcClure  
> 10/22/2009 21:24'!
> scanFor: anObject
> "Scan the key array for the first slot containing either a nil  
> (indicating an empty slot) or an element that matches anObject.  
> Answer the index of that slot or zero if no slot is found. This  
> method will be overridden in various subclasses that have different  
> interpretations for matching elements."
> | element start finish |
> finish := array size.
> start := (anObject primIdentityHash \\ finish) + 1.
>
> "Search from (hash mod size) to the end."
> start to: finish do:
> [:index | ((element := self basicAt: index) == nil or: [element ==  
> anObject])
> ifTrue: [^ index ]].
>
> "Search from 1 to where we started."
> 1 to: start-1 do:
> [:index | ((element := self basicAt: index) == nil or: [element ==  
> anObject])
> ifTrue: [^ index ]].
>
> ^ 0  "No match AND no empty slot"! !
>
>
> !WeakIdentityKeyDictionary methodsFor: 'private' stamp:  
> 'MartinMcClure 10/23/2009 14:54'!
> scanFor: anObject
> "ar 10/21/2000: The method has been copied to this location to  
> indicate that whenever #scanFor: changes #scanForNil: must be  
> changed in the receiver as well."
> "Scan the key array for the first slot containing either a nil  
> (indicating an empty slot) or an element that matches anObject.  
> Answer the index of that slot or zero if no slot is found. This  
> method will be overridden in various subclasses that have different  
> interpretations for matching elements."
> | element start finish hash |
> finish := array size.
> start := (anObject identityHash \\ finish) + 1.
>
> "Search from (hash mod size) to the end."
> start to: finish do:
> [:index | ((element := array at: index) == nil or: [element key ==  
> anObject])
> ifTrue: [^ index ]].
>
> "Search from 1 to where we started."
> 1 to: start-1 do:
> [:index | ((element := array at: index) == nil or: [element key ==  
> anObject])
> ifTrue: [^ index ]].
>
> ^ 0  "No match AND no empty slot"! !
>
> !WeakIdentityKeyDictionary methodsFor: 'private' stamp:  
> 'MartinMcClure 10/23/2009 14:54'!
> scanForNil: anObject
> "Private. Scan the key array for the first slot containing nil  
> (indicating an empty slot). Answer the index of that slot."
> | start finish hash |
> finish := array size.
> start := (anObject identityHash \\ array size) + 1.
>
> "Search from (hash mod size) to the end."
> start to: finish do:
> [:index | (array at: index) == nil ifTrue: [^ index ]].
>
> "Search from 1 to where we started."
> 1 to: start-1 do:
> [:index | (array at: index) == nil ifTrue: [^ index ]].
>
> ^ 0  "No match AND no empty slot"! !
>
>
>
>
>
>
>
> "---------------------Do surgery and rehash before  
> continuing--------------------------"!
>
> | dict method |
> dict := ProtoObject methodDictionary.
> method := dict at: #identityHashTEMP.
> dict at: #identityHash put: method.
> dict := Object methodDictionary.
> method := dict at: #hashTEMP.
> dict at: #identityHash put: method.
>
> Set rehashAllSets.!
>
> "---------- Life should be... better now :-)  
> -----------------------------"!
>
>
>
> !ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure  
> 10/22/2009 22:30'!
> identityHash
> "Answer a SmallInteger whose value is related to the receiver's  
> identity.
> This method must not be overridden, except by SmallInteger.
> Primitive. Fails if the receiver is a SmallInteger. Essential.
> See Object documentation whatIsAPrimitive.
>
> Do not override."
>
> ^self primIdentityHash bitShift: 18! !
>
>
> !Object methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009  
> 22:46'!
> hash
> "Answer a SmallInteger whose value is related to the receiver's  
> identity.
> May be overridden, and should be overridden in any classes that  
> define = "
>
> ^ self primIdentityHash bitShift: 18! !
>
>
> !FixedIdentitySet methodsFor: 'private' stamp: 'MartinMcClure  
> 10/23/2009 14:49'!
> indexOf: anObject
> anObject isNil ifTrue: [self error: 'This class collection cannot  
> handle nil as an element'].
> ^ (anObject primIdentityHash bitAnd: self basicSize - 1) + 1! !
>
>
> !Set class methodsFor: 'sizing' stamp: 'MartinMcClure 10/23/2009  
> 09:44'!
> goodPrimes
> "Answer a sorted array of prime numbers less than one hundred million
> that make good hash table sizes. Should be expanded to more numbers  
> if folks
> want to make larger collections.
> Need to check with Andres' book when I get back to work to see if I  
> remembered
> it right :-)
>
> Generated with this code:
>
> | prevPrime primes goodPrimes |
> goodPrimes := OrderedCollection new.
> primes := Integer largePrimesUpTo: 100000000.
> goodPrimes add: 5.
> prevPrime := 5.
> primes do:
> [:prime | prime > (prevPrime * 4 // 3) ifTrue:
> [| lowByte | lowByte := prime bitAnd: 16rFF.
> (lowByte > 10 and: [lowByte < 245]) ifTrue:
> [goodPrimes add: prime.
> prevPrime := prime]]].
> ^goodPrimes asArray printString"
>
> ^#(5 11 17 23 31 43 59 79 107 149 199 269 359 479 641 857 1151 1549  
> 2069 2767 3691 4931 6577 8779 11717 15629 20849 27799 37087 49451  
> 65951 87943 117259 156347 208463 277961 370619 494167 658897 878539  
> 1171393 1561883 2082527 2776727 3702313 4936423 6581909 8775947  
> 11701267 15601723 20802317 27736427 36981911 49309219 65745677  
> 87660917)!
> ]style[(10 311 405 337)f2b,f2,f1,f2! !
>
> !Set class methodsFor: 'sizing' stamp: 'MartinMcClure 10/23/2009  
> 10:14'!
> goodPrimeAtLeast: lowerLimit
> "Answer the next good prime >= lowerlimit.
> If lowerLimit is larger than the largest known good prime,
> just make it odd."
>
> | primes low mid high prime |
> primes := self goodPrimes.
> low := 1.
> high := primes size.
> lowerLimit > (primes at: high) ifTrue:
> [^lowerLimit even
> ifTrue: [lowerLimit + 1]
> ifFalse: [lowerLimit]].
> [mid := high - low // 2 + low.
> prime := primes at: mid.
> prime < lowerLimit
> ifTrue: [low := mid]
> ifFalse: [high := mid].
> high - low <= 1 ifTrue:
> [^primes at: high].
> prime == lowerLimit ifTrue:
> [^prime]] repeat
>
> !
> ]style[(28 158 411)f2b,f2,f1! !
>
> !Set methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 10:25'!
> growSize
> "Answer what my next higher table size should be"
> ^ self class goodPrimeAtLeast: array size * 2! !
>
>
> !Set methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 10:25'!
> grow
> "Grow the elements array and reinsert the old elements"
> | oldElements |
> oldElements := array.
> array := Array new: self growSize.
> tally := 0.
> oldElements do:
> [:each | each == nil ifFalse: [self noCheckAdd: each]]! !
>
>
> !Set class methodsFor: 'instance creation' stamp: 'MartinMcClure  
> 10/23/2009 10:19'!
> sizeFor: nElements
> "Large enough size to hold nElements with some slop (see fullCheck)"
> nElements <= 0 ifTrue: [^ 5].
> ^ self goodPrimeAtLeast: (nElements+1*4//3)! !
>
>
>
> !WeakSet methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009  
> 10:26'!
> grow
> "Grow the elements array if needed.
> Since WeakSets just nil their slots, alot of the occupied (in the  
> eyes of the set) slots are usually empty. Doubling size if unneeded  
> can lead to BAD performance, therefore we see if reassigning the  
> <live> elements to a Set of similiar size leads to a sufficiently  
> (50% used here) empty set first.
> and reinsert the old elements"
> |oldTally|
> oldTally := tally.
> self growTo: array size.
> oldTally >> 1 < tally ifTrue: [
> self growTo: self growSize]! !
>
>
> !MethodPragmaTest methodsFor: 'testing-primitives' stamp:  
> 'MartinMcClure 10/23/2009 12:37'!
> testPrimitiveIndexed2
> "This test useses the #identityHash primitive."
>
> self compile: '<primitive: 75> ^ #idHash' selector: #idHash.
> self assert: self idHash = self primIdentityHash.! !
>
>
> !SmallInteger reorganize!
> ('arithmetic' * + - / // \\ gcd: quo:)
> ('bit manipulation' bitAnd: bitOr: bitShift: bitXor: hashMultiply  
> highBit highBitOfMagnitude lowBit)
> ('comparing' < <= = > >= hash identityHash primIdentityHash ~=)
> ('converting' as31BitSmallInt asFloat)
> ('copying' clone deepCopy shallowCopy veryDeepCopyWith:)
> ('printing' decimalDigitLength destinationBuffer:  
> numberOfDigitsInBase: printOn:base: printOn:base:nDigits:  
> printString printStringBase: printStringBase:nDigits: threeDigitName)
> ('system primitives' asOop digitAt: digitAt:put: digitLength  
> instVarAt: nextInstance nextObject)
> ('testing' even isLarge odd)
> ('private' fromString:radix: highBitOfPositiveReceiver)
> !
>
>
> !Set class reorganize!
> ('initialization' quickRehashAllSets rehashAllSets)
> ('sizing' goodPrimeAtLeast: goodPrimes)
> ('instance creation' new new: newFrom: sizeFor:)
> !
>
> ProtoObject removeSelector: #identityHashTEMP!
> Object removeSelector: #hashTEMP!
>
> !ProtoObject reorganize!
> ('apply primitives' tryNamedPrimitive tryNamedPrimitive:  
> tryNamedPrimitive:with: tryNamedPrimitive:with:with:  
> tryNamedPrimitive:with:with:with:  
> tryNamedPrimitive:with:with:with:with:  
> tryNamedPrimitive:with:with:with:with:with:  
> tryNamedPrimitive:with:with:with:with:with:with:  
> tryNamedPrimitive:with:with:with:with:with:with:with:  
> tryPrimitive:withArgs:)
> ('closure-prims' privGetInstVar: privRemoteReturnTo:  
> privSetInHolder: privSetInstVar:put: privStoreIn:instVar:)
> ('comparing' == identityHash primIdentityHash ~~)
> ('debugging' doOnlyOnce: flag: rearmOneShot withArgs:executeMethod:)
> ('initialize-release' initialize)
> ('method execution' executeMethod: with:executeMethod:  
> with:with:executeMethod: with:with:with:executeMethod:  
> with:with:with:with:executeMethod:)
> ('objects from disk' rehash)
> ('system primitives' become: cannotInterpret: doesNotUnderstand:  
> nextInstance nextObject)
> ('testing' ifNil: ifNil:ifNotNil: ifNotNil: ifNotNil:ifNil:  
> isInMemory isNil pointsTo:)
> !
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Andres Valloud-4
I should point out that the changesets I sent implement the
scaledIdentityHash approach I just wrote about in the previous email.  
The mutation methodology is more robust as well (note it can also be
used to implement the primIdentityHash approach).  Finally, the prime
table in the changesets I sent is better.  Martin and I need to iron out
a small detail to see if we can get rid of some code.

Andres.


Stéphane Ducasse wrote:

> Martin
>
> are these changes related to the graphs you sent?
> I will have a look after my hospital check.
> Andres? Nicolas?
> Any feedback?
> Martin I imagine that I can package the changes :)
>
>
> Stef
>
> On Oct 24, 2009, at 4:01 AM, Martin McClure wrote:
>
>  
>> OK, here's a filein that improves Pharo hashed collection
>> performance quite a bit. Large collections are much faster, and
>> small ones are pretty much the same speed as before. There are
>> basically two fairly simple changes; the basic structure and
>> algorithms of the collections is unchanged. The changes:
>>
>> 1. Spread identity hash values.
>> 2. Make table sizes prime.
>>
>>
>> File it into PharoCore-1.0-10491rc1.image. It'll take a minute or
>> two since it has to rehash the world halfway through. I don't know
>> how to make another kind of packaging that can do that, so I'll
>> leave that to someone else.
>>
>> After the filein, there are some test failures, most of which do not
>> seem to be *directly* related. I'm hoping someone that knows the
>> affected tests can take a look and comment:
>>
>>
>> Unexpectedly pass ObjectFinalizerTests>>#testFinalizationOfEquals
>>  Not clear why, but this does not seem to be a problem :-)
>>
>> Fails HostWindowTests>>#testOne
>>  But this test fails in the core image on Linux; HostWindows do not
>>  seem to be implemented for Linux.
>>
>> Error on FontTest>>#testMultistringFont
>>  Japanese StrikeFonts have nil characterToGlyphMap,
>>  #createCharacterToGlyphMap answers nil,
>>  not immediately clear how this is supposed to be initialized for
>> fonts
>>  with codepoints > 255.
>>
>> PackageInfoTest>>testKernelPackage
>>  because some method in kernel package for Object is not in Object.
>>  I've changed #hash, so that's probably it.
>>
>> Regards,
>>
>> -Martin
>> 'From Pharo1.0rc1 of 19 October 2009 [Latest update: #10491] on 23
>> October 2009 at 5:54:55 pm'!
>>
>> !ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure
>> 10/22/2009 22:30'!
>> identityHashTEMP
>>       "Answer a SmallInteger whose value is related to the receiver's
>> identity.
>>       This method must not be overridden, except by SmallInteger.
>>       Primitive. Fails if the receiver is a SmallInteger. Essential.
>>       See Object documentation whatIsAPrimitive.
>>
>>       Do not override."
>>
>>       ^self primIdentityHash bitShift: 18! !
>>
>>
>> !Object methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009
>> 22:46'!
>> hashTEMP
>>       "Answer a SmallInteger whose value is related to the receiver's
>> identity.
>>       May be overridden, and should be overridden in any classes that
>> define = "
>>
>>       ^ self primIdentityHash bitShift: 18! !
>>
>>
>> !ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure
>> 10/22/2009 21:13'!
>> primIdentityHash
>>       "Answer a SmallInteger whose value is related to the receiver's
>> identity.
>>       This method must not be overridden, except by SmallInteger.
>>       Primitive. Fails if the receiver is a SmallInteger. Essential.
>>       See Object documentation whatIsAPrimitive.
>>
>>       Do not override."
>>
>>       <primitive: 75>
>>       self primitiveFailed! !
>>
>>
>> !SmallInteger methodsFor: 'comparing' stamp: 'MartinMcClure
>> 10/23/2009 17:53'!
>> primIdentityHash
>>       "Senders of primIdentityHash do it because they expect to get an
>> answer from 1-4095.
>>       So they should not send this to SmallIntegers, but should use
>> #identityHash"
>>
>>       "^self shouldNotImplement"
>>
>>       "...OK, only here for the sake of FixedIdentitySet, which may not
>> need it since it is probably not used for Integers.
>>       And FixedIdentitySet itself may not be needed now that IdentitySets
>> are faster."
>>
>>       ^self! !
>>
>>
>> !IdentityDictionary methodsFor: 'private' stamp: 'MartinMcClure
>> 10/23/2009 14:55'!
>> scanFor: anObject
>>       "Scan the key array for the first slot containing either a nil
>> (indicating an empty slot) or an element that matches anObject.
>> Answer the index of that slot or zero if no slot is found. This
>> method will be overridden in various subclasses that have different
>> interpretations for matching elements."
>>       | finish hash start element |
>>       finish := array size.
>>       start := (anObject identityHash \\ finish) + 1.
>>
>>       "Search from (hash mod size) to the end."
>>       start to: finish do:
>>               [:index | ((element := array at: index) == nil or: [element key ==
>> anObject])
>>                       ifTrue: [^ index ]].
>>
>>       "Search from 1 to where we started."
>>       1 to: start-1 do:
>>               [:index | ((element := array at: index) == nil or: [element key ==
>> anObject])
>>                       ifTrue: [^ index ]].
>>
>>       ^ 0  "No match AND no empty slot"! !
>>
>>
>> !IdentitySet methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009
>> 14:57'!
>> scanFor: anObject
>>       "Scan the key array for the first slot containing either a nil
>> (indicating an empty slot) or an element that matches anObject.
>> Answer the index of that slot or zero if no slot is found. This
>> method will be overridden in various subclasses that have different
>> interpretations for matching elements."
>>       | finish hash start element |
>>       finish := array size.
>>       start := (anObject identityHash \\ finish) + 1.
>>
>>       "Search from (hash mod size) to the end."
>>       start to: finish do:
>>               [:index | ((element := array at: index) == nil or: [element ==
>> anObject])
>>                       ifTrue: [^ index ]].
>>
>>       "Search from 1 to where we started."
>>       1 to: start-1 do:
>>               [:index | ((element := array at: index) == nil or: [element ==
>> anObject])
>>                       ifTrue: [^ index ]].
>>
>>       ^ 0  "No match AND no empty slot"! !
>>
>>
>> !MethodDictionary methodsFor: 'private' stamp: 'MartinMcClure
>> 10/22/2009 21:24'!
>> scanFor: anObject
>>       "Scan the key array for the first slot containing either a nil
>> (indicating an empty slot) or an element that matches anObject.
>> Answer the index of that slot or zero if no slot is found. This
>> method will be overridden in various subclasses that have different
>> interpretations for matching elements."
>>       | element start finish |
>>       finish := array size.
>>       start := (anObject primIdentityHash \\ finish) + 1.
>>
>>       "Search from (hash mod size) to the end."
>>       start to: finish do:
>>               [:index | ((element := self basicAt: index) == nil or: [element ==
>> anObject])
>>                       ifTrue: [^ index ]].
>>
>>       "Search from 1 to where we started."
>>       1 to: start-1 do:
>>               [:index | ((element := self basicAt: index) == nil or: [element ==
>> anObject])
>>                       ifTrue: [^ index ]].
>>
>>       ^ 0  "No match AND no empty slot"! !
>>
>>
>> !WeakIdentityKeyDictionary methodsFor: 'private' stamp:
>> 'MartinMcClure 10/23/2009 14:54'!
>> scanFor: anObject
>>       "ar 10/21/2000: The method has been copied to this location to
>> indicate that whenever #scanFor: changes #scanForNil: must be
>> changed in the receiver as well."
>>       "Scan the key array for the first slot containing either a nil
>> (indicating an empty slot) or an element that matches anObject.
>> Answer the index of that slot or zero if no slot is found. This
>> method will be overridden in various subclasses that have different
>> interpretations for matching elements."
>>       | element start finish hash |
>>       finish := array size.
>>       start := (anObject identityHash \\ finish) + 1.
>>
>>       "Search from (hash mod size) to the end."
>>       start to: finish do:
>>               [:index | ((element := array at: index) == nil or: [element key ==
>> anObject])
>>                       ifTrue: [^ index ]].
>>
>>       "Search from 1 to where we started."
>>       1 to: start-1 do:
>>               [:index | ((element := array at: index) == nil or: [element key ==
>> anObject])
>>                       ifTrue: [^ index ]].
>>
>>       ^ 0  "No match AND no empty slot"! !
>>
>> !WeakIdentityKeyDictionary methodsFor: 'private' stamp:
>> 'MartinMcClure 10/23/2009 14:54'!
>> scanForNil: anObject
>>       "Private. Scan the key array for the first slot containing nil
>> (indicating an empty slot). Answer the index of that slot."
>>       | start finish hash |
>>       finish := array size.
>>       start := (anObject identityHash \\ array size) + 1.
>>
>>       "Search from (hash mod size) to the end."
>>       start to: finish do:
>>               [:index | (array at: index) == nil ifTrue: [^ index ]].
>>
>>       "Search from 1 to where we started."
>>       1 to: start-1 do:
>>               [:index | (array at: index) == nil ifTrue: [^ index ]].
>>
>>       ^ 0  "No match AND no empty slot"! !
>>
>>
>>
>>
>>
>>
>>
>> "---------------------Do surgery and rehash before
>> continuing--------------------------"!
>>
>> | dict method |
>> dict := ProtoObject methodDictionary.
>> method := dict at: #identityHashTEMP.
>> dict at: #identityHash put: method.
>> dict := Object methodDictionary.
>> method := dict at: #hashTEMP.
>> dict at: #identityHash put: method.
>>
>> Set rehashAllSets.!
>>
>> "---------- Life should be... better now :-)
>> -----------------------------"!
>>
>>
>>
>> !ProtoObject methodsFor: 'comparing' stamp: 'MartinMcClure
>> 10/22/2009 22:30'!
>> identityHash
>>       "Answer a SmallInteger whose value is related to the receiver's
>> identity.
>>       This method must not be overridden, except by SmallInteger.
>>       Primitive. Fails if the receiver is a SmallInteger. Essential.
>>       See Object documentation whatIsAPrimitive.
>>
>>       Do not override."
>>
>>       ^self primIdentityHash bitShift: 18! !
>>
>>
>> !Object methodsFor: 'comparing' stamp: 'MartinMcClure 10/22/2009
>> 22:46'!
>> hash
>>       "Answer a SmallInteger whose value is related to the receiver's
>> identity.
>>       May be overridden, and should be overridden in any classes that
>> define = "
>>
>>       ^ self primIdentityHash bitShift: 18! !
>>
>>
>> !FixedIdentitySet methodsFor: 'private' stamp: 'MartinMcClure
>> 10/23/2009 14:49'!
>> indexOf: anObject
>>       anObject isNil ifTrue: [self error: 'This class collection cannot
>> handle nil as an element'].
>>       ^ (anObject primIdentityHash bitAnd: self basicSize - 1) + 1! !
>>
>>
>> !Set class methodsFor: 'sizing' stamp: 'MartinMcClure 10/23/2009
>> 09:44'!
>> goodPrimes
>>       "Answer a sorted array of prime numbers less than one hundred million
>>       that make good hash table sizes. Should be expanded to more numbers
>> if folks
>>       want to make larger collections.
>>       Need to check with Andres' book when I get back to work to see if I
>> remembered
>>       it right :-)
>>
>>       Generated with this code:
>>
>>       | prevPrime primes goodPrimes |
>>       goodPrimes := OrderedCollection new.
>>       primes := Integer largePrimesUpTo: 100000000.
>>       goodPrimes add: 5.
>>       prevPrime := 5.
>>       primes do:
>>               [:prime | prime > (prevPrime * 4 // 3) ifTrue:
>>                       [| lowByte | lowByte := prime bitAnd: 16rFF.
>>                       (lowByte > 10 and: [lowByte < 245]) ifTrue:
>>                               [goodPrimes add: prime.
>>                               prevPrime := prime]]].
>>       ^goodPrimes asArray printString"
>>
>>       ^#(5 11 17 23 31 43 59 79 107 149 199 269 359 479 641 857 1151 1549
>> 2069 2767 3691 4931 6577 8779 11717 15629 20849 27799 37087 49451
>> 65951 87943 117259 156347 208463 277961 370619 494167 658897 878539
>> 1171393 1561883 2082527 2776727 3702313 4936423 6581909 8775947
>> 11701267 15601723 20802317 27736427 36981911 49309219 65745677
>> 87660917)!
>> ]style[(10 311 405 337)f2b,f2,f1,f2! !
>>
>> !Set class methodsFor: 'sizing' stamp: 'MartinMcClure 10/23/2009
>> 10:14'!
>> goodPrimeAtLeast: lowerLimit
>>       "Answer the next good prime >= lowerlimit.
>>       If lowerLimit is larger than the largest known good prime,
>>       just make it odd."
>>
>>       | primes low mid high prime |
>>       primes := self goodPrimes.
>>       low := 1.
>>       high := primes size.
>>       lowerLimit > (primes at: high) ifTrue:
>>               [^lowerLimit even
>>                       ifTrue: [lowerLimit + 1]
>>                       ifFalse: [lowerLimit]].
>>       [mid := high - low // 2 + low.
>>               prime := primes at: mid.
>>               prime < lowerLimit
>>                       ifTrue: [low := mid]
>>                       ifFalse: [high := mid].
>>               high - low <= 1 ifTrue:
>>                       [^primes at: high].
>>               prime == lowerLimit ifTrue:
>>                       [^prime]] repeat
>>
>>       !
>> ]style[(28 158 411)f2b,f2,f1! !
>>
>> !Set methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 10:25'!
>> growSize
>>       "Answer what my next higher table size should be"
>>       ^ self class goodPrimeAtLeast: array size * 2! !
>>
>>
>> !Set methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009 10:25'!
>> grow
>>       "Grow the elements array and reinsert the old elements"
>>       | oldElements |
>>       oldElements := array.
>>       array := Array new: self growSize.
>>       tally := 0.
>>       oldElements do:
>>               [:each | each == nil ifFalse: [self noCheckAdd: each]]! !
>>
>>
>> !Set class methodsFor: 'instance creation' stamp: 'MartinMcClure
>> 10/23/2009 10:19'!
>> sizeFor: nElements
>>       "Large enough size to hold nElements with some slop (see fullCheck)"
>>       nElements <= 0 ifTrue: [^ 5].
>>       ^ self goodPrimeAtLeast: (nElements+1*4//3)! !
>>
>>
>>
>> !WeakSet methodsFor: 'private' stamp: 'MartinMcClure 10/23/2009
>> 10:26'!
>> grow
>>       "Grow the elements array if needed.
>>       Since WeakSets just nil their slots, alot of the occupied (in the
>> eyes of the set) slots are usually    empty. Doubling size if unneeded
>> can lead to BAD performance, therefore we see if reassigning  the
>> <live> elements to a Set of similiar size leads to a sufficiently
>> (50% used here) empty set first.
>>       and reinsert the old elements"
>>       |oldTally|
>>       oldTally := tally.
>>       self growTo: array size.
>>       oldTally >> 1 < tally ifTrue: [
>>       self growTo: self growSize]! !
>>
>>
>> !MethodPragmaTest methodsFor: 'testing-primitives' stamp:
>> 'MartinMcClure 10/23/2009 12:37'!
>> testPrimitiveIndexed2
>>       "This test useses the #identityHash primitive."
>>
>>       self compile: '<primitive: 75> ^ #idHash' selector: #idHash.
>>       self assert: self idHash = self primIdentityHash.! !
>>
>>
>> !SmallInteger reorganize!
>> ('arithmetic' * + - / // \\ gcd: quo:)
>> ('bit manipulation' bitAnd: bitOr: bitShift: bitXor: hashMultiply
>> highBit highBitOfMagnitude lowBit)
>> ('comparing' < <= = > >= hash identityHash primIdentityHash ~=)
>> ('converting' as31BitSmallInt asFloat)
>> ('copying' clone deepCopy shallowCopy veryDeepCopyWith:)
>> ('printing' decimalDigitLength destinationBuffer:
>> numberOfDigitsInBase: printOn:base: printOn:base:nDigits:
>> printString printStringBase: printStringBase:nDigits: threeDigitName)
>> ('system primitives' asOop digitAt: digitAt:put: digitLength
>> instVarAt: nextInstance nextObject)
>> ('testing' even isLarge odd)
>> ('private' fromString:radix: highBitOfPositiveReceiver)
>> !
>>
>>
>> !Set class reorganize!
>> ('initialization' quickRehashAllSets rehashAllSets)
>> ('sizing' goodPrimeAtLeast: goodPrimes)
>> ('instance creation' new new: newFrom: sizeFor:)
>> !
>>
>> ProtoObject removeSelector: #identityHashTEMP!
>> Object removeSelector: #hashTEMP!
>>
>> !ProtoObject reorganize!
>> ('apply primitives' tryNamedPrimitive tryNamedPrimitive:
>> tryNamedPrimitive:with: tryNamedPrimitive:with:with:
>> tryNamedPrimitive:with:with:with:
>> tryNamedPrimitive:with:with:with:with:
>> tryNamedPrimitive:with:with:with:with:with:
>> tryNamedPrimitive:with:with:with:with:with:with:
>> tryNamedPrimitive:with:with:with:with:with:with:with:
>> tryPrimitive:withArgs:)
>> ('closure-prims' privGetInstVar: privRemoteReturnTo:
>> privSetInHolder: privSetInstVar:put: privStoreIn:instVar:)
>> ('comparing' == identityHash primIdentityHash ~~)
>> ('debugging' doOnlyOnce: flag: rearmOneShot withArgs:executeMethod:)
>> ('initialize-release' initialize)
>> ('method execution' executeMethod: with:executeMethod:
>> with:with:executeMethod: with:with:with:executeMethod:
>> with:with:with:with:executeMethod:)
>> ('objects from disk' rehash)
>> ('system primitives' become: cannotInterpret: doesNotUnderstand:
>> nextInstance nextObject)
>> ('testing' ifNil: ifNil:ifNotNil: ifNotNil: ifNotNil:ifNil:
>> isInMemory isNil pointsTo:)
>> !
>>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>    
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> .
>
>  

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Martin McClure-2
In reply to this post by Stéphane Ducasse
Stéphane Ducasse wrote:
> Martin
>
> are these changes related to the graphs you sent?

Yes, you should be able to duplicate the graphs after filing in the code
I sent. Sorry for not giving the two the same subject line; I was in too
much of a hurry that night.

But the code I sent isn't quite ready to integrate; see below.

> I will have a look after my hospital check.
> Andres? Nicolas?
> Any feedback?

My own feedback to my code:
Last night I discovered two problems with the filein I sent:
* It's a Unix full of linefeeds, so creates lousy-looking (though fast
:-) code when filed in.

* There's a typo that leaves an identityHash method in Object's method
dictionary, where it does not belong.



Andres sent some improvements to my code to the list Sun, 25 Oct 2009
03:29:31 -0700. The major changes to my code are:

* His list of 'good primes' is better than mine. I am heartily in favor
of this change.

* His update procedure is much more careful to not upset a running
system. The new code changes hashing, and so requires rehashing all of
the existing hashed collections in the system. My code depends on
nothing much else going on in the system during a critical part of the
upgrade; Andres' updating code is more complex, but is intended to be
safe (and as far as I can tell is safe) to be stopped at any point in
the upgrade and the system will continue to run. Which approach you want
to use depends on how you will package the change for users, I suppose.

* I increased (by bitShift: 18) the range of values answered by
#identityHash, and introduced a new #primIdentityHash method that
answers the old limited-range values. Andres took an alternative
approach; he left #identityHash alone and introduced a new
#scaledIdentityHash with the increased range.

On this last change, I'd like some feedback on which way the community
would like to go. Actually changing #identityHash, as I did, seems to me
to be the cleaner answer going forward. Leaving #identityHash alone, as
Andres did, has less chance of breaking existing non-core code.

Andres and I discussed this issue last night. I'm still in favor of
changing #identityHash, though I'm certainly not 100% sure that's the
best way to go. I believe that Andres is still in favor of the other
approach. I hope he'll contribute to this discussion.


> Martin I imagine that I can package the changes :)

Great, thanks! Once we figure out which approaches to take, either
Andres or I will get you some final code to package.

Regards,

-Martin


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Nicolas Cellier
In reply to this post by Stéphane Ducasse
2009/10/28 Stéphane Ducasse <[hidden email]>:

> Martin
>
> are these changes related to the graphs you sent?
> I will have a look after my hospital check.
> Andres? Nicolas?
> Any feedback?
> Martin I imagine that I can package the changes :)
>
>
> Stef
>

This has been pretty well explained by Martin and Andres.
The decision you have to make is :

- choose Martin change, make speed improvment for most senders of
#identityHash, but eventually break a few senders  and let package
maintainers fix it (example Magma)
- choose Andres change, assure 100% compatibility, let the
responsibility to package maintainers to use new message for improving
speed.

In both cases, package maintainer might have to maintain different
branch for Squeak and Pharo, but I guess the solution would be adopted
soon in Squeak/trunk.

I would tend to be conservative, but I recently took the opposite path
with #keys and #selectors in trunk, so I just can't give you my
personal preference, it's 50-50...
Whatever the choice, #identityHash usage is worth a review by package
maintainers anyway.

Note that this is closely related to
http://bugs.squeak.org/view.php?id=1876 and
http://code.google.com/p/pharo/issues/detail?id=213
Amazing the issue is still there when workarounds are known for so
long... So please do something!

Nicolas

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Nicolas Cellier
After-thoughts: my opinion is:
Martin solution is more pragmatical : it is tailored for getting most
improvment with minimal change in system.
But formally, I prefer Andres design for it's clarity.
- I do not like the idea that #identityHash and #primIdentityHash do
behave differently
- #scaledIdentityHash does clearly express itself on the contrary
But that turns into german discussions ;)

Nicolas

2009/10/29 Nicolas Cellier <[hidden email]>:

> 2009/10/28 Stéphane Ducasse <[hidden email]>:
>> Martin
>>
>> are these changes related to the graphs you sent?
>> I will have a look after my hospital check.
>> Andres? Nicolas?
>> Any feedback?
>> Martin I imagine that I can package the changes :)
>>
>>
>> Stef
>>
>
> This has been pretty well explained by Martin and Andres.
> The decision you have to make is :
>
> - choose Martin change, make speed improvment for most senders of
> #identityHash, but eventually break a few senders  and let package
> maintainers fix it (example Magma)
> - choose Andres change, assure 100% compatibility, let the
> responsibility to package maintainers to use new message for improving
> speed.
>
> In both cases, package maintainer might have to maintain different
> branch for Squeak and Pharo, but I guess the solution would be adopted
> soon in Squeak/trunk.
>
> I would tend to be conservative, but I recently took the opposite path
> with #keys and #selectors in trunk, so I just can't give you my
> personal preference, it's 50-50...
> Whatever the choice, #identityHash usage is worth a review by package
> maintainers anyway.
>
> Note that this is closely related to
> http://bugs.squeak.org/view.php?id=1876 and
> http://code.google.com/p/pharo/issues/detail?id=213
> Amazing the issue is still there when workarounds are known for so
> long... So please do something!
>
> Nicolas
>

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Stéphane Ducasse
Ok since there were some other discussions I think that andres and  
martin got a consensus
on the solution (I had the impression that the one of martin was  
prefered).
So as soon as the code is ok we will integrate that.

Stef



On Oct 29, 2009, at 10:39 AM, Nicolas Cellier wrote:

> After-thoughts: my opinion is:
> Martin solution is more pragmatical : it is tailored for getting most
> improvment with minimal change in system.
> But formally, I prefer Andres design for it's clarity.
> - I do not like the idea that #identityHash and #primIdentityHash do
> behave differently
> - #scaledIdentityHash does clearly express itself on the contrary
> But that turns into german discussions ;)
>
> Nicolas
>
> 2009/10/29 Nicolas Cellier <[hidden email]>:
>> 2009/10/28 Stéphane Ducasse <[hidden email]>:
>>> Martin
>>>
>>> are these changes related to the graphs you sent?
>>> I will have a look after my hospital check.
>>> Andres? Nicolas?
>>> Any feedback?
>>> Martin I imagine that I can package the changes :)
>>>
>>>
>>> Stef
>>>
>>
>> This has been pretty well explained by Martin and Andres.
>> The decision you have to make is :
>>
>> - choose Martin change, make speed improvment for most senders of
>> #identityHash, but eventually break a few senders  and let package
>> maintainers fix it (example Magma)
>> - choose Andres change, assure 100% compatibility, let the
>> responsibility to package maintainers to use new message for  
>> improving
>> speed.
>>
>> In both cases, package maintainer might have to maintain different
>> branch for Squeak and Pharo, but I guess the solution would be  
>> adopted
>> soon in Squeak/trunk.
>>
>> I would tend to be conservative, but I recently took the opposite  
>> path
>> with #keys and #selectors in trunk, so I just can't give you my
>> personal preference, it's 50-50...
>> Whatever the choice, #identityHash usage is worth a review by package
>> maintainers anyway.
>>
>> Note that this is closely related to
>> http://bugs.squeak.org/view.php?id=1876 and
>> http://code.google.com/p/pharo/issues/detail?id=213
>> Amazing the issue is still there when workarounds are known for so
>> long... So please do something!
>>
>> Nicolas
>>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Stéphane Ducasse
In reply to this post by Nicolas Cellier
Nicolas

I do not internet now so I cannot check (hospital bed no wifi :)).
But yes we want to move on. We waited too long to invent the future :)

Stef

On Oct 29, 2009, at 10:39 AM, Nicolas Cellier wrote:

>> Note that this is closely related to
>> http://bugs.squeak.org/view.php?id=1876 and
>> http://code.google.com/p/pharo/issues/detail?id=213
>> Amazing the issue is still there when workarounds are known for so
>> long... So please do something!
>


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Andres Valloud-4
In reply to this post by Nicolas Cellier
Nicolas,

Would you like Martin's approach better if the selector was
#basicIdentityHash instead of #primIdentityHash?  Is it a matter of
naming only, or is there something else?

Andres.

Nicolas Cellier wrote:

> After-thoughts: my opinion is:
> Martin solution is more pragmatical : it is tailored for getting most
> improvment with minimal change in system.
> But formally, I prefer Andres design for it's clarity.
> - I do not like the idea that #identityHash and #primIdentityHash do
> behave differently
> - #scaledIdentityHash does clearly express itself on the contrary
> But that turns into german discussions ;)
>
> Nicolas
>
> 2009/10/29 Nicolas Cellier <[hidden email]>:
>  
>> 2009/10/28 Stéphane Ducasse <[hidden email]>:
>>    
>>> Martin
>>>
>>> are these changes related to the graphs you sent?
>>> I will have a look after my hospital check.
>>> Andres? Nicolas?
>>> Any feedback?
>>> Martin I imagine that I can package the changes :)
>>>
>>>
>>> Stef
>>>
>>>      
>> This has been pretty well explained by Martin and Andres.
>> The decision you have to make is :
>>
>> - choose Martin change, make speed improvment for most senders of
>> #identityHash, but eventually break a few senders  and let package
>> maintainers fix it (example Magma)
>> - choose Andres change, assure 100% compatibility, let the
>> responsibility to package maintainers to use new message for improving
>> speed.
>>
>> In both cases, package maintainer might have to maintain different
>> branch for Squeak and Pharo, but I guess the solution would be adopted
>> soon in Squeak/trunk.
>>
>> I would tend to be conservative, but I recently took the opposite path
>> with #keys and #selectors in trunk, so I just can't give you my
>> personal preference, it's 50-50...
>> Whatever the choice, #identityHash usage is worth a review by package
>> maintainers anyway.
>>
>> Note that this is closely related to
>> http://bugs.squeak.org/view.php?id=1876 and
>> http://code.google.com/p/pharo/issues/detail?id=213
>> Amazing the issue is still there when workarounds are known for so
>> long... So please do something!
>>
>> Nicolas
>>
>>    
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> .
>
>  

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Andres Valloud-4
In reply to this post by Nicolas Cellier
(note that I mentioned Magma just for the sake of illustration for my
argument... I do not know whether either approach will affect it)

Nicolas Cellier wrote:

> 2009/10/28 Stéphane Ducasse <[hidden email]>:
>  
>> Martin
>>
>> are these changes related to the graphs you sent?
>> I will have a look after my hospital check.
>> Andres? Nicolas?
>> Any feedback?
>> Martin I imagine that I can package the changes :)
>>
>>
>> Stef
>>
>>    
>
> This has been pretty well explained by Martin and Andres.
> The decision you have to make is :
>
> - choose Martin change, make speed improvment for most senders of
> #identityHash, but eventually break a few senders  and let package
> maintainers fix it (example Magma)
> - choose Andres change, assure 100% compatibility, let the
> responsibility to package maintainers to use new message for improving
> speed.
>
> In both cases, package maintainer might have to maintain different
> branch for Squeak and Pharo, but I guess the solution would be adopted
> soon in Squeak/trunk.
>
> I would tend to be conservative, but I recently took the opposite path
> with #keys and #selectors in trunk, so I just can't give you my
> personal preference, it's 50-50...
> Whatever the choice, #identityHash usage is worth a review by package
> maintainers anyway.
>
> Note that this is closely related to
> http://bugs.squeak.org/view.php?id=1876 and
> http://code.google.com/p/pharo/issues/detail?id=213
> Amazing the issue is still there when workarounds are known for so
> long... So please do something!
>
> Nicolas
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
>  

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Martin McClure-2
In reply to this post by Andres Valloud-4
Andres Valloud wrote:

> Nicolas,
>
> Would you like Martin's approach better if the selector was
> #basicIdentityHash instead of #primIdentityHash?  Is it a matter of
> naming only, or is there something else?
>
> Andres.
>
> Nicolas Cellier wrote:
>> After-thoughts: my opinion is:
>> Martin solution is more pragmatical : it is tailored for getting most
>> improvment with minimal change in system.
>> But formally, I prefer Andres design for it's clarity.
>> - I do not like the idea that #identityHash and #primIdentityHash do
>> behave differently
>> - #scaledIdentityHash does clearly express itself on the contrary
>> But that turns into german discussions ;)

My thoughts in choosing the naming:

#identityHash
   Answers a value with a good range, suitable for general use, can be
used in code that is portable across Smalltalk dialects. Today the range
is not good across all dialects, but maybe this will improve if we start
the movement here in Pharo).

#primIdentityHash
   Used (almost) only by ProtoObject>>identityHash. Has a limited range;
that range might get better when VM/image format changes. Could also be
used by packages that want to do something very special and don't care
that they will not be portable across dialects. The use in
MethodDictionary is an example of this special non-portable use.

I'd certainly be open to a better name for #primIdentityHash.

Regards,

-Martin

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Nicolas Cellier
In reply to this post by Stéphane Ducasse
2009/10/29 Stéphane Ducasse <[hidden email]>:
> Nicolas
>
> I do not internet now so I cannot check (hospital bed no wifi :)).
> But yes we want to move on. We waited too long to invent the future :)
>
> Stef
>
> On Oct 29, 2009, at 10:39 AM, Nicolas Cellier wrote:
>

Smalltalk apart, I wish you a healthy future.

>>> Note that this is closely related to
>>> http://bugs.squeak.org/view.php?id=1876 and
>>> http://code.google.com/p/pharo/issues/detail?id=213
>>> Amazing the issue is still there when workarounds are known for so
>>> long... So please do something!
>>
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Stéphane Ducasse
>>
>
> Smalltalk apart, I wish you a healthy future.

Me too. The news are good apparently my problems was a false positive
of the investigation tools. I should say that I like false positives  
now.
Still it makes me think about life and stress during this period :)

Stef

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Andres Valloud-4
In reply to this post by Stéphane Ducasse
Ok, I can prepare the checkpointed changesets for Martin's changes then.

Stéphane Ducasse wrote:

> Ok since there were some other discussions I think that andres and  
> martin got a consensus
> on the solution (I had the impression that the one of martin was  
> prefered).
> So as soon as the code is ok we will integrate that.
>
> Stef
>
>
>
> On Oct 29, 2009, at 10:39 AM, Nicolas Cellier wrote:
>
>  
>> After-thoughts: my opinion is:
>> Martin solution is more pragmatical : it is tailored for getting most
>> improvment with minimal change in system.
>> But formally, I prefer Andres design for it's clarity.
>> - I do not like the idea that #identityHash and #primIdentityHash do
>> behave differently
>> - #scaledIdentityHash does clearly express itself on the contrary
>> But that turns into german discussions ;)
>>
>> Nicolas
>>
>> 2009/10/29 Nicolas Cellier <[hidden email]>:
>>    
>>> 2009/10/28 Stéphane Ducasse <[hidden email]>:
>>>      
>>>> Martin
>>>>
>>>> are these changes related to the graphs you sent?
>>>> I will have a look after my hospital check.
>>>> Andres? Nicolas?
>>>> Any feedback?
>>>> Martin I imagine that I can package the changes :)
>>>>
>>>>
>>>> Stef
>>>>
>>>>        
>>> This has been pretty well explained by Martin and Andres.
>>> The decision you have to make is :
>>>
>>> - choose Martin change, make speed improvment for most senders of
>>> #identityHash, but eventually break a few senders  and let package
>>> maintainers fix it (example Magma)
>>> - choose Andres change, assure 100% compatibility, let the
>>> responsibility to package maintainers to use new message for  
>>> improving
>>> speed.
>>>
>>> In both cases, package maintainer might have to maintain different
>>> branch for Squeak and Pharo, but I guess the solution would be  
>>> adopted
>>> soon in Squeak/trunk.
>>>
>>> I would tend to be conservative, but I recently took the opposite  
>>> path
>>> with #keys and #selectors in trunk, so I just can't give you my
>>> personal preference, it's 50-50...
>>> Whatever the choice, #identityHash usage is worth a review by package
>>> maintainers anyway.
>>>
>>> Note that this is closely related to
>>> http://bugs.squeak.org/view.php?id=1876 and
>>> http://code.google.com/p/pharo/issues/detail?id=213
>>> Amazing the issue is still there when workarounds are known for so
>>> long... So please do something!
>>>
>>> Nicolas
>>>
>>>      
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>    
>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> .
>
>  

_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
Reply | Threaded
Open this post in threaded view
|

Re: Hashed collection improvements: Some code

Stéphane Ducasse
oh this would be good.

Stef

On Oct 31, 2009, at 7:19 PM, Andres Valloud wrote:

> Ok, I can prepare the checkpointed changesets for Martin's changes  
> then.
>
> Stéphane Ducasse wrote:
>> Ok since there were some other discussions I think that andres and
>> martin got a consensus
>> on the solution (I had the impression that the one of martin was
>> prefered).
>> So as soon as the code is ok we will integrate that.
>>
>> Stef
>>
>>
>>
>> On Oct 29, 2009, at 10:39 AM, Nicolas Cellier wrote:
>>
>>
>>> After-thoughts: my opinion is:
>>> Martin solution is more pragmatical : it is tailored for getting  
>>> most
>>> improvment with minimal change in system.
>>> But formally, I prefer Andres design for it's clarity.
>>> - I do not like the idea that #identityHash and #primIdentityHash do
>>> behave differently
>>> - #scaledIdentityHash does clearly express itself on the contrary
>>> But that turns into german discussions ;)
>>>
>>> Nicolas
>>>
>>> 2009/10/29 Nicolas Cellier <[hidden email]>:
>>>
>>>> 2009/10/28 Stéphane Ducasse <[hidden email]>:
>>>>
>>>>> Martin
>>>>>
>>>>> are these changes related to the graphs you sent?
>>>>> I will have a look after my hospital check.
>>>>> Andres? Nicolas?
>>>>> Any feedback?
>>>>> Martin I imagine that I can package the changes :)
>>>>>
>>>>>
>>>>> Stef
>>>>>
>>>>>
>>>> This has been pretty well explained by Martin and Andres.
>>>> The decision you have to make is :
>>>>
>>>> - choose Martin change, make speed improvment for most senders of
>>>> #identityHash, but eventually break a few senders  and let package
>>>> maintainers fix it (example Magma)
>>>> - choose Andres change, assure 100% compatibility, let the
>>>> responsibility to package maintainers to use new message for
>>>> improving
>>>> speed.
>>>>
>>>> In both cases, package maintainer might have to maintain different
>>>> branch for Squeak and Pharo, but I guess the solution would be
>>>> adopted
>>>> soon in Squeak/trunk.
>>>>
>>>> I would tend to be conservative, but I recently took the opposite
>>>> path
>>>> with #keys and #selectors in trunk, so I just can't give you my
>>>> personal preference, it's 50-50...
>>>> Whatever the choice, #identityHash usage is worth a review by  
>>>> package
>>>> maintainers anyway.
>>>>
>>>> Note that this is closely related to
>>>> http://bugs.squeak.org/view.php?id=1876 and
>>>> http://code.google.com/p/pharo/issues/detail?id=213
>>>> Amazing the issue is still there when workarounds are known for so
>>>> long... So please do something!
>>>>
>>>> Nicolas
>>>>
>>>>
>>> _______________________________________________
>>> Pharo-project mailing list
>>> [hidden email]
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>>
>>
>>
>> _______________________________________________
>> Pharo-project mailing list
>> [hidden email]
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>> .
>>
>>
>
> _______________________________________________
> Pharo-project mailing list
> [hidden email]
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
[hidden email]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project