[squeak-dev] The Trunk: Collections-mt.602.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jan 20 07:27:44 UTC 2015


Marcel Taeumel uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-mt.602.mcz

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

Name: Collections-mt.602
Author: mt
Time: 20 January 2015, 8:27:19.919 am
UUID: 96d6fefa-c902-7640-bd09-c17016199e81
Ancestors: Collections-ul.601

Merged improvements for OrderedDictionary from inbox (ul.601).

Fixed problem in (mt.600 version) #copyFrom:to: with memory allocation. Preferred this over ul.601 because it is faster (8 per second vs. 12 per second).

d := OrderedDictionary new.
1 to: 1000000 do: [:ea | d at: ea put: nil].
[d copyFrom: 250000 to: 750000] bench.

=============== Diff against Collections-mt.600 ===============

Item was added:
+ ----- Method: FloatCollection>>asFloatArray (in category 'adding') -----
+ asFloatArray
+ 	"Optimized version"
+ 
+ 	^array copyFrom: firstIndex to: lastIndex!

Item was changed:
  Dictionary subclass: #OrderedDictionary
+ 	instanceVariableNames: 'order'
- 	instanceVariableNames: 'order lastIndex'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Collections-Sequenceable'!
  
  !OrderedDictionary commentStamp: 'mt 1/16/2015 10:42' prior: 0!
  I am an ordered dictionary. I have an additional index (called 'order') to keep track of the insertion order of my associations.
  
  The read access is not affected by the additional index.
  
  The index is updated in O(1) [time] when inserting new keys. For present keys, that insertion involves actions in O(n) to move the respective element to the end of the order.
  
  The growth operation compacts the index and takes O(n) additional time.
  
  NOTE: This is still no instance of SequenceableCollection. Having this, some protocols are missing and may require working on #associations, which is an Array and thus sequenceable.!

Item was changed:
  ----- Method: OrderedDictionary>>associationsDo: (in category 'enumerating') -----
  associationsDo: aBlock
  	"Iterate over the order instead of the internal array."
  
+ 	order from: 1 to: tally do: aBlock!
- 	lastIndex = 0 ifTrue: [^ self].
- 	1 to: lastIndex do: [:index |
- 		(order at: index) ifNotNil: [:element |
- 			aBlock value: element]].!

Item was changed:
  ----- Method: OrderedDictionary>>atIndex: (in category 'accessing') -----
  atIndex: integer
  
+ 	integer > tally ifTrue: [ self error: 'indices are out of bounds' ].
+ 	^order at: integer!
- 	^ self atIndex: integer ifAbsent: [self errorOutOfBounds]!

Item was changed:
  ----- Method: OrderedDictionary>>atIndex:ifAbsent: (in category 'accessing') -----
  atIndex: integer ifAbsent: exceptionBlock
  	"As we are sequenceable, provide index-based access."
  
+ 	integer > tally ifTrue: [ ^exceptionBlock value ].
+ 	^order at: integer ifAbsent: exceptionBlock!
- 	| found |
- 	found := 0.
- 	self associationsDo: [:element |
- 		(found := found + 1) = integer ifTrue: [
- 			^ element]].
- 
- 	^ exceptionBlock value!

Item was changed:
  ----- Method: OrderedDictionary>>atNewIndex:put: (in category 'private') -----
  atNewIndex: index put: anObject
  
+ 	super atNewIndex: index put: anObject.
+ 	order at: tally put: anObject
+ 	!
- 	lastIndex = order size ifTrue: [
- 		self fixEmptySlots].
- 
- 	lastIndex := lastIndex + 1.
- 	order at: lastIndex put: anObject.
- 	
- 	super atNewIndex: index put: anObject.!

Item was changed:
  ----- Method: OrderedDictionary>>copyFrom:to: (in category 'copying') -----
  copyFrom: startIndex to: endIndex 
  	"Answer a copy of the receiver that contains elements from position
  	startIndex to endIndex."
  
- 	self fixEmptySlots.
  	^ self shallowCopy postCopyFrom: startIndex to: endIndex!

Item was removed:
- ----- Method: OrderedDictionary>>fillOrderFrom: (in category 'private') -----
- fillOrderFrom: anArray
- 
- 	| arraySize |
- 	arraySize := lastIndex.
- 	lastIndex := 0.
- 	1 to: arraySize do: [:index |
- 		(anArray at: index) ifNotNil: [:object |
- 			lastIndex := lastIndex + 1.
- 			order at: lastIndex put: object]].!

Item was removed:
- ----- Method: OrderedDictionary>>fixEmptySlots (in category 'private') -----
- fixEmptySlots
- 	"Remove all nil slots in the order index to avoid overflow."
- 
- 	lastIndex = tally ifTrue: [^ self].
- 	self fillOrderFrom: order.!

Item was changed:
  ----- Method: OrderedDictionary>>growTo: (in category 'private') -----
  growTo: anInteger
  
  	| oldOrder |
  	super growTo: anInteger.
  	oldOrder := order.
  	"Grow only to 75%. See #atNewIndex:put: in HashedCollection."
+ 	order := self class arrayType new: anInteger + 1 * 3 // 4.
+ 	order
+ 		replaceFrom: 1
+ 		to: tally
+ 		with: oldOrder
+ 		startingAt: 1!
- 	order := self class arrayType new: (anInteger * (3/4)) ceiling.
- 	self fillOrderFrom: oldOrder.!

Item was changed:
  ----- Method: OrderedDictionary>>initialize: (in category 'private') -----
  initialize: n
  
  	super initialize: n.
+ 	order := self class arrayType new: n + 1 * 3 // 4!
- 	order := self class arrayType new: (n * (3/4)) ceiling.
- 	lastIndex := 0.!

Item was changed:
  ----- Method: OrderedDictionary>>isSorted (in category 'sorting') -----
  isSorted
+ 	"Return true if the receiver is sorted by #<=."
- 	"Return true if the receiver's keys are sorted by #<=."
  	
- 	self fixEmptySlots.
  	^ order
  		isSortedBetween: 1
+ 		and: tally!
- 		and: lastIndex!

Item was changed:
  ----- Method: OrderedDictionary>>postCopy (in category 'copying') -----
  postCopy
  	"We must not copy associations again but retrieve them from the array, which is already a copy. See super."
  
  	super postCopy.
+ 	order := order copy.
+ 	1 to: tally do: [ :index |
+ 		order at: index put: (array at: (self scanFor: (order at: index) key)) ]!
- 	order := order collect: [:association |
- 		association ifNotNil: [array at: (self scanFor: association key)]].!

Item was changed:
  ----- Method: OrderedDictionary>>postCopyFrom:to: (in category 'copying') -----
  postCopyFrom: startIndex to: endIndex
  	"Adapted from SequenceableCollection and OrderedCollection."
  
+ 	| oldOrder |	
- 	| oldOrder newArraySize newOrderSize |
- 	newArraySize := self class goodPrimeAtLeast: ((endIndex - startIndex + 1) * (5/4) "add 25%") ceiling.
- 	newOrderSize := (newArraySize * (3/4)) ceiling. "remove 25%"
- 	
  	oldOrder := order.
+ 	array := self class arrayType
+ 		new: (self class goodPrimeAtLeast: endIndex - startIndex + 1 * 4 // 3). "fill 75% to 100%"
+ 	order := self class arrayType
+ 		new: array size * 3 // 4. "remove 25%"
- 	order := self class arrayType new: newOrderSize.
- 	array := self class arrayType new: newArraySize.
  
  	startIndex to: endIndex do: [:index | | element |
  		element := (oldOrder at: index) copy.
  		order at: index - startIndex + 1 put: element.
  		array at: (self scanFor: element key) put: element].
  
+ 	tally := endIndex - startIndex + 1.!
- 	lastIndex := endIndex - startIndex + 1.
- 	tally := lastIndex.
- 
- 	
- !

Item was changed:
  ----- Method: OrderedDictionary>>removeKey:ifAbsent: (in category 'removing') -----
  removeKey: key ifAbsent: aBlock
  
+ 	| result |
+ 	result := super removeKey: key ifAbsent: [ ^aBlock value ].
+ 	(self scanOrderFor: key) ifNotNil: [ :index |
+ 		order 
+ 			replaceFrom: index
+ 			to: tally
+ 			with: order
+ 			startingAt: index + 1 ].
+ .	order at: tally + 1 put: nil.
+ 	^result!
- 	(self scanOrderFor: key) ifNotNil: [:index |
- 		order at: index put: nil].
- 	^ super removeKey: key ifAbsent: aBlock!

Item was changed:
  ----- Method: OrderedDictionary>>scanOrderFor: (in category 'private') -----
  scanOrderFor: anObject
  
+ 	1 to: tally do: [ :index |
+ 		(order at: index) key = anObject ifTrue: [ ^index ] ].
+ 	^nil!
- 	1 to: lastIndex do: [:index |
- 		| element |
- 		((element := order at: index) notNil and: [anObject = element key])
- 			ifTrue: [^ index]].
- 	
- 	^ nil!

Item was changed:
  ----- Method: OrderedDictionary>>sort (in category 'sorting') -----
  sort
  
+ 	self sort: nil!
- 	self sort: [:a1 :a2| a1 key <= a2 key].!

Item was changed:
  ----- Method: OrderedDictionary>>sort: (in category 'sorting') -----
  sort: aSortBlock
  	"Like in OrderedCollection, sort the associations according to the sort block."
  
+ 	tally <= 1 ifTrue: [ ^self ].
+ 	order
+ 		mergeSortFrom: 1
+ 		to: tally
+ 		by: aSortBlock!
- 	self ifNotEmpty: [
- 		self fixEmptySlots.
- 		order
- 			mergeSortFrom: 1
- 			to: lastIndex
- 			by: aSortBlock].!



More information about the Squeak-dev mailing list