On 3 October 2010 03:13, Henrik Sperre Johansen
<henrik.s.johan...@veloxit.no> wrote:
>  On 02.10.2010 19:01, Igor Stasenko wrote:
>>
>> On 2 October 2010 19:47, Stéphane Ducasse<stephane.duca...@inria.fr>
>>  wrote:
>>>
>>> Hi igor
>>>
>>> do you understand why the previous definition was
>>>
>>> cachedDefinitions
>>>        Definitions ifNil: [Definitions := WeakIdentityKeyDictionary new.
>>>  WeakArray addWeakDependent: Definitions].
>>>        ^ Definitions
>>>
>> i don't. :)
>>
>> It just a way to free memory as fast as possible.
>> But its really not worth spending so much CPU in order to save few
>> bytes of memory.
>
> Without registering the dict for finalization, the values won't ever be
> removed with the current implementation.

They are removed. After each package load/unload operation.
I don't see a reason to do this more often.

> Which can be somewhat hampering to performance once you have lots of
> nil-keyed elements all stashed from index 1 and onwards after a rehash.
>
In Pharo, weak dict knows how to reuse expired associations:

at: key put: anObject
        "Set the value at key to be anObject.  If key is not found, create a new
        entry for key and set is value to anObject. Answer anObject."
        | index element |
        key isNil ifTrue:[^anObject].
        index := self scanForEmpty: key.
        
        "There should always be room."
        index = 0 ifTrue: [ self error: 'No space left in dictionary' ].
        
        element := array at: index.
        element == nil
                ifTrue: [self atNewIndex: index put: (WeakKeyAssociation key: 
key
value: anObject)]
                ifFalse: [
                        element expired ifTrue: [ tally := tally + 1].
                        element key: key.
                        element value: anObject.
                        self fullCheck.
                ].
        ^ anObject

> Cheers,
> Henry
>
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project



-- 
Best regards,
Igor Stasenko AKA sig.

_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to