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

commits at source.squeak.org commits at source.squeak.org
Thu Nov 5 07:14:59 UTC 2009


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

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

Name: Collections-ar.183
Author: ar
Time: 4 November 2009, 11:14:39 am
UUID: 2e07a36b-f72b-6a42-a58b-72a620a3d515
Ancestors: Collections-ul.179, Collections-ul.180, Collections-ul.181, Collections-ul.182

Merging Collections-ul.179, Collections-ul.180, Collections-ul.181, Collections-ul.182:

- added: String >> #hashWithInitialHash: which lets the string to decide which hash implementation to use, this way ByteStrings can use the primitive implementation instead of the general one

- speed up mergesort for the general case (using <= for comparison), sacrificing < 1% performance for other cases
- allow symbols to be evaluated as comparison blocks. For example: sorting an Array in descening order can be as simple as: array sort: #>=, it's also faster than using a block.

- simplified Dictionary >> #keysSortedSafely 
- simplified WeakRegistry >> #keys
- save a few bytecodes in #scanFor: of identity based collections when their size is between 4097 and 8191

- fix: WeakKeyDictionary >> #finalizeValues: (increment the tally, and make sure that we don't lose the key)
- collect the objects which should be finalized into an IdentitySet instead of an OrderedCollection in WeakRegistry >> #finalizeValues this should give better performance in WeakKeyDictionary >> #finalizeValues:

=============== Diff against Collections-nice.178 ===============

Item was changed:
  ----- Method: ArrayedCollection>>sort: (in category 'sorting') -----
  sort: aSortBlock 
  	"Sort this array using aSortBlock. The block should take two arguments
+ 	and return true if the first element should preceed the second one.
+ 	If aSortBlock is nil then <= is used for comparison."
- 	and return true if the first element should preceed the second one."
  
  	self
  		mergeSortFrom: 1
  		to: self size
  		by: aSortBlock!

Item was changed:
  ----- Method: IdentityDictionary>>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 hash |
+ 	array size >= 8192
- 	array size > 4096
  		ifTrue: [ hash := anObject identityHash * (array size // 4096) ]
  		ifFalse: [ hash := anObject identityHash ].
  	index := start := hash \\ array size + 1.
  	[ 
  		| element |
  		((element := array at: index) == nil or: [ element key == anObject ])
  			ifTrue: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was changed:
  ----- Method: ArrayedCollection>>mergeFirst:middle:last:into:by: (in category 'sorting') -----
  mergeFirst: first middle: middle last: last into: dst by: aBlock
  	"Private. Merge the sorted ranges [first..middle] and [middle+1..last] 
  	of the receiver into the range [first..last] of dst."
  
  	| i1 i2 val1 val2 out |
  	i1 := first.
  	i2 := middle + 1.
  	val1 := self at: i1.
  	val2 := self at: i2.
  	out := first - 1.  "will be pre-incremented"
  
  	"select 'lower' half of the elements based on comparator"
+ 	[ (i1 <= middle) and: [ i2 <= last ] ] whileTrue: 	[
+ 		(aBlock 
+ 			ifNil: [ val1 <= val2 ]
+ 			ifNotNil: [ aBlock value: val1 value: val2 ])
+ 				ifTrue: [
+ 					dst at: (out := out + 1) put: val1.
- 	[(i1 <= middle) and: [i2 <= last]] whileTrue:
- 		[(aBlock value: val1 value: val2)
- 			ifTrue: [dst at: (out := out + 1) put: val1.
  					val1 := self at: (i1 := i1 + 1)]
+ 				ifFalse: [
+ 					dst at: (out := out + 1) put: val2.
+ 					(i2 := i2 + 1) <= last ifTrue: [
+ 						val2 := self at: i2 ] ] ].
- 			ifFalse: [dst at: (out := out + 1) put: val2.
- 					i2 := i2 + 1.
- 					i2 <= last ifTrue: [val2 := self at: i2]]].
  
  	"copy the remaining elements"
  	i1 <= middle
  		ifTrue: [dst replaceFrom: out + 1 to: last with: self startingAt: i1]
  		ifFalse: [dst replaceFrom: out + 1 to: last with: self startingAt: i2]!

Item was changed:
  ----- Method: WeakRegistry>>finalizeValues (in category 'finalization') -----
  finalizeValues
  	"Some of our elements may have gone away. Look for those and activate the associated executors."
  	| finiObjects |
  	finiObjects := nil.
  	"First collect the objects."
+ 	self protected: [
+ 		valueDictionary associationsDo: [ :assoc |
+ 			assoc key ifNil: [
+ 				(finiObjects ifNil: [ finiObjects := IdentitySet new ])
+ 					add: assoc value ] ].
+ 		finiObjects ifNotNil: [ valueDictionary finalizeValues: finiObjects ] ].
- 	self protected:[
- 		valueDictionary associationsDo:[:assoc|
- 			assoc key isNil ifTrue:[
- 				finiObjects isNil 
- 					ifTrue:[finiObjects := OrderedCollection with: assoc value]
- 					ifFalse:[finiObjects add: assoc value]]
- 		].
- 		finiObjects isNil ifFalse:[valueDictionary finalizeValues: finiObjects asArray].
- 	].
  	"Then do the finalization"
+ 	finiObjects ifNil: [ ^self ].
+ 	finiObjects do: [ :each | each finalize ]!
- 	finiObjects isNil ifTrue:[^self].
- 	finiObjects do:[:each| each finalize].
- !

Item was changed:
  ----- Method: WeakIdentityKeyDictionary>>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 hash |
+ 	array size  >= 8192
- 	array size > 4096
  		ifTrue: [ hash := anObject identityHash * (array size // 4096) ]
  		ifFalse: [ hash := anObject identityHash ].
  	index := start := hash \\ array size + 1.
  	[ 
  		| element |
  		((element := array at: index) == nil or: [ element key == anObject ])
  			ifTrue: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was added:
+ ----- Method: Symbol>>value:value: (in category 'evaluating') -----
+ value: anObject value: anotherObject
+ 
+ 	^anObject perform: self with: anotherObject!

Item was changed:
  ----- Method: ArrayedCollection>>sort (in category 'sorting') -----
  sort
  	"Sort this array into ascending order using the '<=' operator."
  
+ 	self sort: nil!
- 	self sort: [:a :b | a <= b]!

Item was changed:
  ----- Method: OrderedCollection>>sort: (in category 'sorting') -----
  sort: aSortBlock 
+ 	"Sort this collection using aSortBlock. The block should take two arguments
+ 	and return true if the first element should preceed the second one.
+ 	If aSortBlock is nil then <= is used for comparison."
- 	"Sort this array using aSortBlock. The block should take two arguments
- 	and return true if the first element should preceed the second one."
  
  	self ifNotEmpty: [
  		array
  			mergeSortFrom: firstIndex
  			to: lastIndex
  			by: aSortBlock ]!

Item was added:
+ ----- Method: String>>hashWithInitialHash: (in category 'comparing') -----
+ hashWithInitialHash: initialHash
+ 	
+ 	^ self class stringHash: self initialHash: initialHash!

Item was changed:
  ----- Method: Dictionary>>keysSortedSafely (in category 'accessing') -----
  keysSortedSafely
+ 	"Answer a sorted Array containing the receiver's keys."
- 	"Answer an Array containing the receiver's keys."
  	
+ 	 ^self keys sort: [ :x :y |
- 	| sortedKeys |
- 	sortedKeys := Array new: self size streamContents: [ :stream |
- 		self keysDo: [ :each | stream nextPut: each ] ].
- 	sortedKeys sort: [ :x :y |
  		"Should really be use <obj, string, num> compareSafely..."
  		((x isString and: [ y isString ])
  			or: [ x isNumber and: [ y isNumber ] ])
  			ifTrue: [ x < y ]
  			ifFalse: [ x class == y class
  				ifTrue: [ x printString < y printString ]
  				ifFalse: [ x class name < y class name ] ] ].
+ !
- 	^sortedKeys!

Item was changed:
  ----- Method: WeakRegistry>>keys (in category 'accessing') -----
  keys
+ 
+ 	^self protected: [ valueDictionary keys ]!
- 	^self protected:[
- 		Array streamContents:[:s| valueDictionary keysDo:[:key| s nextPut: key]]].!

Item was changed:
  ----- Method: WeakKeyDictionary>>finalizeValues: (in category 'finalization') -----
  finalizeValues: finiObjects
  	"Remove all associations with key == nil and value is in finiObjects.
  	This method is folded with #rehash for efficiency."
  	
  	| oldArray |
  	oldArray := array.
  	array := Array new: oldArray size.
  	tally := 0.
  	1 to: array size do:[ :i |
  		| association |
  		(association := oldArray at: i) ifNotNil: [
+ 			| key |
+ 			((key := association key) == nil and: [ "Don't let the key go away"
+ 				finiObjects includes: association value ])
+ 					ifFalse: [
+ 						array 
+ 							at: (self scanForEmptySlotFor: key) 
+ 							put: association.
+ 						tally := tally + 1 ] ] ]!
- 			(association key == nil and: [ finiObjects includes: association value ])
- 				ifFalse:[
- 					array 
- 						at: (self scanForEmptySlotFor: association key) 
- 						put: association ] ] ]!

Item was changed:
  ----- Method: OrderedCollection>>sort (in category 'sorting') -----
  sort
  	"Sort this array into ascending order using the '<=' operator."
  
+ 	self sort: nil!
- 	self sort: [:a :b | a <= b]!

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 hash |
+ 	array size >= 8192
- 	array size > 4096
  		ifTrue: [ hash := anObject identityHash * (array size // 4096) ]
  		ifFalse: [ hash := anObject identityHash ].
  	index := start := hash \\ array size + 1.
  	[ 
  		| element |
  		((element := array at: index) == nil or: [ element == anObject ])
  			ifTrue: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

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 hash |
+ 	array size >= 8192
- 	array size > 4096
  		ifTrue: [ hash := anObject identityHash * (array size // 4096) ]
  		ifFalse: [ hash := anObject identityHash ].
  	index := start := hash \\ array size + 1.
  	[ 
  		| element |
  		((element := array at: index) == nil or: [ (keyBlock value: element) == anObject ])
  			ifTrue: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!



More information about the Packages mailing list