[Pkg] The Trunk: Traits-nice.248.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Dec 24 10:48:36 UTC 2009


Nicolas Cellier uploaded a new version of Traits to project The Trunk:
http://source.squeak.org/trunk/Traits-nice.248.mcz

==================== Summary ====================

Name: Traits-nice.248
Author: nice
Time: 24 December 2009, 11:49:10 am
UUID: 557593d7-1db7-2347-bf40-2d40e3b91f55
Ancestors: Traits-nice.247

Move FixedIdentitySet off the Array hierarchy.
Provide a fast implementation using MethodDictionary tricks
- handles collisions (instead of blindly ignoring the entry)
- eventually grow.

I did not understand previous design decision...
The conflict just did happen (I put a halt: and caught one in Object...)
According to my own scale, make it work > make it fast.

Rationale about the new design:
#grow costs, but I think it is user responsibility to fix a reasonnable capacity.
collisions handling should not cost much (except above 4096 entries)

If any expert knowing the reasons for this class and knowing how to fire the profiling tests could have a look, thanks...

=============== Diff against Traits-nice.247 ===============

Item was changed:
+ Collection variableSubclass: #FixedIdentitySet
+ 	instanceVariableNames: 'tally capacity hashShift'
- Array variableSubclass: #FixedIdentitySet
- 	instanceVariableNames: 'tally capacity'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Traits-Requires'!
  
+ !FixedIdentitySet commentStamp: 'nice 12/24/2009 11:46' prior: 0!
+ This is a fast implementation of fixed size identity sets.
+ Same algorithm as MethodDictionary are used, and thus FixedIdentitySet is to IdentitySet what MethodDictionary is to IdentityDictionary.
+ The main features are:
+ 1) do not use an array instance variable so as to fast-up creation and every access
+ 2) due to the fixed allocated size, growing costs an expensive #become: operation. Preallocate me with care.
+ 3) my size is a power of two so the the hashing algorithm be most efficient.
+ 4) for maximum random access efficiency, at least half the storage area is always kept empty
- !FixedIdentitySet commentStamp: 'NS 5/26/2005 13:00' prior: 0!
- This is a fast but lazy implementation of fixed size identity sets. The two main difference to regular identity sets are:
- 
- 1) These identity sets have a fixed size. If they are full, adding another element doesn't have any effect.
- 2) No rehashing. If two elements were to be stored on the same position in the underlying array, one of them is simply discarded.
  
+ Unlike MethodDictionary, this class will scale a bit better over the 4096 basicSize limit inherent to identityHash, thanks to a proper bitShift.!
- As a consequence of (1) and (2), these identity sets are very fast!! Note that this class inherits form Array. This is not clean but reduces memory overhead when instances are created.!

Item was added:
+ ----- Method: FixedIdentitySet>>removeAll (in category 'removing') -----
+ removeAll
+ 	tally = 0 ifTrue: [^self].
+ 	1 to: self basicSize do: [:i | self basicAt: i put: nil].
+ 	tally := 0!

Item was changed:
+ ----- Method: FixedIdentitySet>>add: (in category 'adding') -----
- ----- Method: FixedIdentitySet>>add: (in category 'accessing') -----
  add: anObject
+ 	| index |
+ 	index := self scanFor: anObject.
+ 	(self basicAt: index)
+ 		ifNil: [
+ 			self basicAt: index put: anObject.
+ 			tally := tally + 1.
+ 			self isFull ifTrue: [ self grow ]]
+ 		"ifNotNil: [] already inside".
+ 	^anObject!
- 	| index old |
- 	self isFull ifTrue: [^ false].
- 	index := self indexOf: anObject.
- 	old := self basicAt: index.
- 	old == anObject ifTrue: [^ true].
- 	old ifNotNil: [^ false].
- 	self basicAt: index put: anObject.
- 	tally := tally + 1.
- 	^ true!

Item was changed:
+ ----- Method: FixedIdentitySet>>addAll:notIn: (in category 'adding') -----
- ----- Method: FixedIdentitySet>>addAll:notIn: (in category 'accessing') -----
  addAll: aCollection notIn: notCollection
  	aCollection do: [:each | 
- 		self isFull ifTrue: [^ self].
  		(notCollection includes: each) ifFalse: [self add: each].
  	].!

Item was changed:
  ----- Method: FixedIdentitySet class>>with:with:with:with:with: (in category 'instance creation') -----
  with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject
  	"Answer an instance of me, containing the five arguments as the elements."
  
+ 	^ (self new: 5)
- 	^ self new
  		add: firstObject;
  		add: secondObject;
  		add: thirdObject;
  		add: fourthObject;
  		add: fifthObject;
  		yourself!

Item was changed:
  ----- Method: FixedIdentitySet class>>with:with:with:with:with:with: (in category 'instance creation') -----
  with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject with: sixthObject
  	"Answer an instance of me, containing the six arguments as the elements."
  
+ 	^ (self new: 6)
- 	^ self new
  		add: firstObject;
  		add: secondObject;
  		add: thirdObject;
  		add: fourthObject;
  		add: fifthObject;
  		add: sixthObject;
  		yourself!

Item was changed:
+ ----- Method: FixedIdentitySet class>>new (in category 'instance creation') -----
- ----- Method: FixedIdentitySet class>>new (in category 'constants') -----
  new
  	^ self new: self defaultSize!

Item was added:
+ ----- Method: FixedIdentitySet>>grow (in category 'private') -----
+ grow
+ 	| newSelf |
+ 	newSelf := self species new: capacity * 2.  "This will double the capacity"
+ 	self do: [ :anObject | newSelf add: anObject ].
+ 	self become: newSelf!

Item was changed:
+ ----- Method: FixedIdentitySet>>includes: (in category 'testing') -----
+ includes: aSymbol
+ 	"This override assumes that pointsTo is a fast primitive"
+ 
+ 	aSymbol ifNil: [^ false].
+ 	^ self pointsTo: aSymbol!
- ----- Method: FixedIdentitySet>>includes: (in category 'accessing') -----
- includes: anObject
- 	^ (self basicAt: (self indexOf: anObject)) == anObject!

Item was added:
+ ----- Method: FixedIdentitySet>>fixCollisionsFrom: (in category 'private') -----
+ fixCollisionsFrom: start
+ 	"The element at start has been removed and replaced by nil.
+ 	This method moves forward from there, relocating any entries
+ 	that had been placed below due to collisions with this one."
+ 
+ 	| key index mask |
+ 	index := start.
+ 	mask := self basicSize - 1.
+ 	[ (key := self basicAt: (index := (index bitAnd: mask) + 1)) == nil ] whileFalse: [
+ 		| newIndex |
+ 		(newIndex := self scanFor: key) = index ifFalse: [
+ 			| element |
+ 			element := self basicAt: index.
+ 			self basicAt: index put: (self basicAt: newIndex).
+ 			self basicAt: newIndex put: element.] ]!

Item was changed:
+ ----- Method: FixedIdentitySet class>>new: (in category 'instance creation') -----
- ----- Method: FixedIdentitySet class>>new: (in category 'constants') -----
  new: anInteger
+ 	^ (self basicNew: (self arraySizeForCapacity: anInteger)) initializeCapacity: anInteger!
- 	^ (super new: (self arraySizeForCapacity: anInteger)) initializeCapacity: anInteger!

Item was changed:
+ ----- Method: FixedIdentitySet>>remove:ifAbsent: (in category 'removing') -----
- ----- Method: FixedIdentitySet>>remove:ifAbsent: (in category 'accessing') -----
  remove: anObject ifAbsent: aBlock
+ 	| index element |
+ 	index := self scanFor: anObject.
+ 	(element := self basicAt: index) ifNil: [ ^aBlock value ].
+ 	self basicAt: index put: nil.
+ 	tally := tally - 1.
+ 	self fixCollisionsFrom: index.
+ 	^element!
- 	| index |
- 	index := self indexOf: anObject.
- 	^ (self basicAt: index) == anObject 
- 		ifTrue: [self basicAt: index put: nil. tally := tally - 1. anObject]
- 		ifFalse: [aBlock value].!

Item was added:
+ ----- Method: FixedIdentitySet>>rehash (in category 'private') -----
+ rehash
+ 	| newSelf |
+ 	newSelf := self species new: self size.
+ 	self do: [ :anObject | newSelf add: anObject ].
+ 	^newSelf!

Item was changed:
  ----- Method: FixedIdentitySet>>initializeCapacity: (in category 'initialize-release') -----
  initializeCapacity: anInteger
  	tally := 0.
+ 	capacity := anInteger.
+ 	hashShift := self basicSize highBit - 4096 highBit max: 0!
- 	capacity := anInteger.!

Item was changed:
+ ----- Method: FixedIdentitySet class>>arraySizeForCapacity: (in category 'private') -----
- ----- Method: FixedIdentitySet class>>arraySizeForCapacity: (in category 'constants') -----
  arraySizeForCapacity: anInteger
  	"Because of the hash performance, the array size is always a power of 2 
  	and at least twice as big as the capacity anInteger"
  
  	^ anInteger <= 0 
  		ifTrue: [0]
  		ifFalse: [1 << (anInteger << 1 - 1) highBit].!

Item was added:
+ ----- Method: FixedIdentitySet>>scanFor: (in category 'private') -----
+ 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 raise an error if no slot is found. This method will be overridden in various subclasses that have different interpretations for matching elements."
+ 
+ 	| index start mask |
+ 	anObject ifNil: [self error: 'This class collection cannot handle nil as an element'].
+ 	mask := self basicSize - 1.
+ 	index := start := ((anObject identityHash bitShift: hashShift) bitAnd: mask) + 1.
+ 	[ 
+ 		| element |
+ 		((element := self basicAt: index) == nil or: [ element == anObject ])
+ 			ifTrue: [ ^index ].
+ 		(index := (index bitAnd: mask) + 1) = start ] whileFalse.
+ 	self errorNoFreeSpace!

Item was removed:
- ----- Method: FixedIdentitySet>>destructiveAdd: (in category 'accessing') -----
- destructiveAdd: anObject
- 	| index old |
- 	self isFull ifTrue: [^ false].
- 	index := self indexOf: anObject.
- 	old := self basicAt: index.
- 	self basicAt: index put: anObject.
- 	old ifNil: [tally := tally + 1].
- 	^ true!

Item was removed:
- ----- Method: FixedIdentitySet>>notFull (in category 'testing') -----
- notFull
- 	^ tally < capacity!

Item was removed:
- ----- Method: FixedIdentitySet>>addAll: (in category 'accessing') -----
- addAll: aCollection
- 	aCollection do: [:each | 
- 		self isFull ifTrue: [^ self].
- 		self add: each.
- 	].!

Item was removed:
- ----- Method: FixedIdentitySet>>indexOf: (in category 'private') -----
- indexOf: anObject
- 	anObject isNil ifTrue: [self error: 'This class collection cannot handle nil as an element'].
- 	^ (anObject identityHash bitAnd: self basicSize - 1) + 1!



More information about the Packages mailing list