[Pkg] The Trunk: Collections-ar.288.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Feb 2 04:25:52 UTC 2010


Andreas Raab uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ar.288.mcz

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

Name: Collections-ar.288
Author: ar
Time: 1 February 2010, 8:25:27.355 pm
UUID: 50bb9e1d-6487-fa4a-b39b-72d5e7290090
Ancestors: Collections-ar.287

Sets with nil: Merge code from http://bugs.squeak.org/view.php?id=7413 before it rots even more.

=============== Diff against Collections-ar.287 ===============

Item was changed:
  ----- Method: IdentitySet>>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 |
  	index := start := anObject scaledIdentityHash \\ array size + 1.
  	[ 
  		| element |
+ 		((element := array at: index) == nil or: [ element enclosedSetElement == anObject ])
- 		((element := array at: index) == nil or: [ element == anObject ])
  			ifTrue: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was changed:
  ----- Method: Set>>noCheckNoGrowFillFrom: (in category 'private') -----
  noCheckNoGrowFillFrom: anArray
  	"Add the elements of anArray except nils to me assuming that I don't contain any of them, they are unique and I have more free space than they require."
  
  	1 to: anArray size do: [ :index |
  		(anArray at: index) ifNotNil: [ :object |
  			array
+ 				at: (self scanForEmptySlotFor: object enclosedSetElement)
- 				at: (self scanForEmptySlotFor: object)
  				put: object ] ]!

Item was changed:
  ----- Method: Set>>add: (in category 'adding') -----
  add: newObject
  	"Include newObject as one of the receiver's elements, but only if
  	not already present. Answer newObject."
  
  	| index |
- 	newObject ifNil: [self error: 'Sets cannot meaningfully contain nil as an element'].
  	index := self scanFor: newObject.
+ 	(array at: index) ifNil: [self atNewIndex: index put: newObject asSetElement].
- 	(array at: index) ifNil: [self atNewIndex: index put: newObject].
  	^ newObject!

Item was changed:
  ----- Method: Set>>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."
  
  	| element index |
  	index := start.
  	[ (element := array at: (index := index \\ array size + 1)) == nil ] whileFalse: [
  		| newIndex |
+ 		(newIndex := self scanFor: element enclosedSetElement) = index ifFalse: [
- 		(newIndex := self scanFor: element) = index ifFalse: [
  			array swap: index with: newIndex ] ]!

Item was changed:
  ----- Method: Set>>like: (in category 'accessing') -----
  like: anObject
  	"Answer an object in the receiver that is equal to anObject,
  	nil if no such object is found. Relies heavily on hash properties"
  
+ 	^(array at: (self scanFor: anObject)) ifNotNil:[:obj| obj enclosedSetElement]!
- 	^array at: (self scanFor: anObject)!

Item was added:
+ ----- Method: SetElement classSide>>initialize (in category 'class initialization') -----
+ initialize
+ 	NilElement := self with: nil.
+ !

Item was added:
+ ----- Method: SetElement>>enclosedSetElement: (in category 'accessing') -----
+ enclosedSetElement: anObject
+ 	enclosedElement := anObject!

Item was changed:
  ----- Method: Set>>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 |
  	index := start := anObject hash \\ array size + 1.
  	[ 
  		| element |
+ 		((element := array at: index) == nil or: [ element enclosedSetElement = anObject ])
- 		((element := array at: index) == nil or: [ element = anObject ])
  			ifTrue: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was added:
+ ----- Method: Set>>like:ifAbsent: (in category 'accessing') -----
+ like: anObject ifAbsent: aBlock
+ 	"Answer an object in the receiver that is equal to anObject,
+ 	or evaluate the block if not found. Relies heavily on hash properties"
+ 	| element |
+ 	element := array at: (self scanFor: anObject).
+ 	^ element ifNil: [ aBlock value ] ifNotNil: [ element enclosedSetElement ]!

Item was added:
+ ----- Method: SetElement>>= (in category 'comparing') -----
+ = anObject
+ 	^ anObject class = self class and: [ enclosedElement = anObject enclosedSetElement ]
+ !

Item was added:
+ ----- Method: SetElement>>hash (in category 'comparing') -----
+ hash
+ 	^ enclosedElement hash
+ !

Item was changed:
  ----- Method: PluggableSet>>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 |
  	index := start := (hashBlock
  		ifNil: [ anObject hash ]
  		ifNotNil: [ hashBlock value: anObject ]) \\ array size + 1.
  	[ 
  		| element |
  		((element := array at: index) == nil or: [
  			equalBlock
+ 				ifNil: [ element enclosedSetElement = anObject ]
+ 				ifNotNil: [ equalBlock value: element enclosedSetElement value: anObject ] ])
- 				ifNil: [ element = anObject ]
- 				ifNotNil: [ equalBlock value: element value: anObject ] ])
  			ifTrue: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was added:
+ ----- Method: SetElement>>asSetElement (in category 'converting') -----
+ asSetElement
+ 	"A receiver has to be included into a set, as a distinct object.
+ 	We need to wrap receiver in own turn, otherwise #enclosedSetElement will return wrong object for that set"
+ 	^ SetElement with: self!

Item was added:
+ ----- Method: SetElement classSide>>withNil (in category 'accessing') -----
+ withNil
+ 	^ NilElement
+ !

Item was added:
+ ----- Method: SetElement>>enclosedSetElement (in category 'accessing') -----
+ enclosedSetElement
+ 	^ enclosedElement!

Item was changed:
  ----- Method: Set>>do: (in category 'enumerating') -----
  do: aBlock 
  
  	tally = 0 ifTrue: [ ^self ].
  	1 to: array size do: [ :index |
  		(array at: index) ifNotNil: [ :element |
+ 			aBlock value: element enclosedSetElement] ]!
- 			aBlock value: element ] ]!

Item was added:
+ Object subclass: #SetElement
+ 	instanceVariableNames: 'enclosedElement'
+ 	classVariableNames: 'NilElement'
+ 	poolDictionaries: ''
+ 	category: 'Collections-Support'!

Item was added:
+ ----- Method: SetElement classSide>>with: (in category 'instance creation') -----
+ with: anObject
+ 	^ self new enclosedSetElement: anObject!



More information about the Packages mailing list