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

commits at source.squeak.org commits at source.squeak.org
Tue Feb 2 05:39:15 UTC 2010


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

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

Name: Collections-ar.289
Author: ar
Time: 1 February 2010, 9:38:20.103 pm
UUID: 87822d82-f84f-c743-be96-cb1c4e3c9df2
Ancestors: Collections-ar.288

Complete Set with nil support by providing proper modifications to KeyedSet and WeakSet.

=============== Diff against Collections-ar.288 ===============

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

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

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

Item was changed:
  ----- Method: KeyedSet>>member: (in category 'adding') -----
  member: newObject
  	"Include newObject as one of the receiver's elements, if already exists just return it"
  
  	| index |
- 	newObject ifNil: [self error: 'Sets cannot meaningfully contain nil as an element'].
  	index := self scanFor: (keyBlock value: newObject).
+ 	(array at: index) ifNotNil: [ :element | ^element enclosedSetElement].
+ 	self atNewIndex: index put: newObject asSetElement.
- 	(array at: index) ifNotNil: [ :element | ^element ].
- 	self atNewIndex: index put: newObject.
  	^ newObject!

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

Item was changed:
  ----- Method: KeyedSet>>noCheckAdd: (in category 'private') -----
  noCheckAdd: anObject
  
  	self deprecated: 'This method should not be used anymore.'.
+ 	array at: (self scanFor: (keyBlock value: anObject)) put: anObject asSetElement.
- 	array at: (self scanFor: (keyBlock value: anObject)) put: anObject.
  	tally := tally + 1!

Item was changed:
  ----- Method: WeakSet>>fixCollisionsFrom: (in category 'private') -----
  fixCollisionsFrom: start
  	"The element at start has been removed and replaced by flag.
  	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)) == flag ] whileFalse: [
  		| newIndex |
+ 		(newIndex := self scanFor: element enclosedSetElement) = index ifFalse: [
- 		(newIndex := self scanFor: element) = index ifFalse: [
  			array swap: index with: newIndex ] ]
  !

Item was changed:
  ----- Method: KeyedSet>>at:ifAbsent: (in category 'accessing') -----
  at: key ifAbsent: aBlock 
  	"Answer the value associated with the key or, if key isn't found,
  	answer the result of evaluating aBlock."
  
+ 	^(array at: (self scanFor: key)) ifNil: [ aBlock value ] ifNotNil:[:obj| obj enclosedSetElement]!
- 	^(array at: (self scanFor: key)) ifNil: [ aBlock value ]!

Item was changed:
  ----- Method: WeakSet>>scanForLoadedSymbol: (in category 'private') -----
  scanForLoadedSymbol: 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 |
  
  	start := (anObject hash \\ array size) + 1.
  	finish := array size.
  
  	"Search from (hash mod size) to the end."
  	start to: finish do:
+ 		[:index | ((element := array at: index) == flag or: [element enclosedSetElement asString = anObject asString])
- 		[:index | ((element := array at: index) == flag or: [element asString = anObject asString])
  			ifTrue: [^ index ]].
  
  	"Search from 1 to where we started."
  	1 to: start-1 do:
+ 		[:index | ((element := array at: index) == flag or: [element enclosedSetElement asString = anObject asString])
- 		[:index | ((element := array at: index) == flag or: [element asString = anObject asString])
  			ifTrue: [^ index ]].
  
  	^ 0  "No match AND no empty slot"!

Item was changed:
  ----- Method: WeakSet>>do:after: (in category 'public') -----
  do: aBlock after: anElement
  
  	| startIndex |
  	tally = 0 ifTrue: [ ^self ].
  	startIndex := anElement
  		ifNil: [ 0 ]
  		ifNotNil: [ self scanFor: anElement ].
  	startIndex + 1 to: array size do: [ :index |
  		(array at: index) ifNotNil: [ :object |
  			object == flag ifFalse: [
+ 				aBlock value: object enclosedSetElement] ] ]!
- 				aBlock value: object ] ] ]!

Item was changed:
  ----- Method: WeakSet>>scanFor: (in category 'private') -----
  scanFor: anObject
  	"Scan the key array for the first slot containing either flag (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) == flag or: [ element enclosedSetElement = anObject ])
- 		((element := array at: index) == flag or: [ element = anObject ])
  			ifTrue: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was changed:
  ----- Method: KeyedSet>>removeKey:ifAbsent: (in category 'removing') -----
  removeKey: key ifAbsent: aBlock
  
  	| index obj |
  	index := self scanFor: key.
  	(obj := array at: index) == nil ifTrue: [ ^ aBlock value ].
  	array at: index put: nil.
  	tally := tally - 1.
  	self fixCollisionsFrom: index.
+ 	^ obj enclosedSetElement!
- 	^ obj!

Item was changed:
  ----- Method: KeyedSet>>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: (keyBlock value: object enclosedSetElement))
- 				at: (self scanForEmptySlotFor: (keyBlock value: object))
  				put: object ] ]!

Item was changed:
  ----- Method: KeyedSet>>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: (keyBlock value: 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: KeyedSet>>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: (keyBlock value: element enclosedSetElement)) = index ifFalse: [
- 		(newIndex := self scanFor: (keyBlock value: element)) = index ifFalse: [
  			array swap: index with: newIndex ] ]!

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

Item was changed:
  ----- Method: WeakSet>>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"
  
  	| element |
  	^(element  := array at: (self scanFor: anObject)) == flag
+ 		ifFalse: [ element enclosedSetElement]!
- 		ifFalse: [ element ]!

Item was changed:
  ----- Method: WeakSet>>collect: (in category 'enumerating') -----
  collect: aBlock
  
  	| newSet |
  	newSet := self species new: self size.
  	tally = 0 ifTrue: [ ^newSet ].
  	1 to: array size do: [ :index |
  		(array at: index) ifNotNil: [ :object |
  			object == flag ifFalse: [
+ 				newSet add: (aBlock value: object enclosedSetElement) ] ] ].
- 				newSet add: (aBlock value: object) ] ] ].
  	^newSet!



More information about the Packages mailing list