[squeak-dev] The Inbox: Collections-nice.464.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Oct 29 20:54:36 UTC 2011


Nicolas Cellier uploaded a new version of Collections to project The Inbox:
http://source.squeak.org/inbox/Collections-nice.464.mcz

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

Name: Collections-nice.464
Author: nice
Time: 29 October 2011, 10:54:15.683 pm
UUID: 1a03ae5c-e979-4e30-b808-e7a26fcf4e97
Ancestors: Collections-ul.463

Optimize RunArray.
This should not be noticeable for Text, but as a general library, it's important for any other potential use.
Also move it off ArrayedCollection which serves nothing to such subclass.

=============== Diff against Collections-ul.463 ===============

Item was changed:
+ SequenceableCollection subclass: #RunArray
- ArrayedCollection subclass: #RunArray
  	instanceVariableNames: 'runs values lastIndex lastRun lastOffset'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Collections-Arrayed'!
  
  !RunArray commentStamp: '<historical>' prior: 0!
  My instances provide space-efficient storage of data which tends to be constant over long runs of the possible indices. Essentially repeated values are stored singly and then associated with a "run" length that denotes the number of consecutive occurrences of the value.
  
  My two important variables are
  	runs	An array of how many elements are in each run
  	values	An array of what the value is over those elements
  
  The variables lastIndex, lastRun and lastOffset cache the last access
  so that streaming through RunArrays is not an N-squared process.
  
  Many complexities of access can be bypassed by using the method
  	RunArray withStartStopAndValueDo:!

Item was changed:
  ----- Method: RunArray class>>newFrom: (in category 'instance creation') -----
  newFrom: aCollection 
  	"Answer an instance of me containing the same elements as aCollection."
  
+ 	| runs values lastRun lastValue |
+ 	runs := (Array new: aCollection size // 2) writeStream.
+ 	values := (Array new: aCollection size // 2) writeStream.
+ 	lastRun := 0.
+ 	lastValue := Object new.
+ 	aCollection do: [:x | 
+ 		lastValue = x
+ 			ifTrue: [lastRun := lastRun + 1]
+ 			ifFalse:
+ 				[lastRun > 0
+ 					ifTrue:
+ 						[runs nextPut: lastRun.
+ 						values nextPut: lastValue].
+ 				lastRun := 1.
+ 				lastValue := x]].
+ 	lastRun > 0
+ 		ifTrue:
+ 			[runs nextPut: lastRun.
+ 			values nextPut: lastValue].
+ 	^self basicNew setRuns: runs contents setValues: values contents
- 	| newCollection |
- 	newCollection := self new.
- 	aCollection do: [:x | newCollection addLast: x].
- 	^newCollection
  
  "	RunArray newFrom: {1. 2. 2. 3}
  	{1. $a. $a. 3} as: RunArray
  	({1. $a. $a. 3} as: RunArray) values
  "!

Item was changed:
+ ----- Method: RunArray>>= (in category 'comparing') -----
- ----- Method: RunArray>>= (in category 'accessing') -----
  = otherArray 
  	"Test if all my elements are equal to those of otherArray"
  
+ 	self == otherArray ifTrue: [^true].
+ 	self species == otherArray species ifFalse: [^ false].
  	(otherArray isMemberOf: RunArray) ifFalse: [^ self hasEqualElements: otherArray].
  
  	"Faster test between two RunArrays"
   	^ (runs hasEqualElements: otherArray runs)
  		and: [values hasEqualElements: otherArray values]!

Item was added:
+ ----- Method: RunArray>>add:withOccurrences: (in category 'adding') -----
+ add: newObject withOccurrences: anInteger
+ 	"Add value as the last element of the receiver, the given number of times"
+ 	anInteger <= 0 ifTrue: [ ^self ].
+ 	lastIndex := nil.  "flush access cache"
+ 	(runs size=0 or: [values last ~= newObject])
+ 	  ifTrue:
+ 		[runs := runs copyWith: anInteger.
+ 		values := values copyWith: newObject]
+ 	  ifFalse:
+ 		[runs at: runs size put: runs last + anInteger]!

Item was changed:
  ----- Method: RunArray>>addLast:times: (in category 'adding') -----
  addLast: value  times: times
  	"Add value as the last element of the receiver, the given number of times"
+ 	self deprecated: 'use add:withOccurrences:'.
+ 	^self add: value withOccurrences: times!
- 	times = 0 ifTrue: [ ^self ].
- 	lastIndex := nil.  "flush access cache"
- 	(runs size=0 or: [values last ~= value])
- 	  ifTrue:
- 		[runs := runs copyWith: times.
- 		values := values copyWith: value]
- 	  ifFalse:
- 		[runs at: runs size put: runs last+times]!

Item was added:
+ ----- Method: RunArray>>allSatisfy: (in category 'enumerating') -----
+ allSatisfy: aBlock 
+ 	"Only evaluate once per run"
+ 
+ 	^values allSatisfy: aBlock!

Item was added:
+ ----- Method: RunArray>>anySatisfy: (in category 'enumerating') -----
+ anySatisfy: aBlock 
+ 	"Only evaluate once per run"
+ 
+ 	^values anySatisfy: aBlock!

Item was added:
+ ----- Method: RunArray>>asBag (in category 'converting') -----
+ asBag
+ 	| aBag |
+ 	aBag := Bag new: values size.
+ 	self runsAndValuesDo: [:run :value |
+ 		aBag add: value withOccurrences: run].
+ 	^aBag!

Item was added:
+ ----- Method: RunArray>>asSet (in category 'converting') -----
+ asSet
+ 	^values asSet!

Item was added:
+ ----- Method: RunArray>>collect: (in category 'enumerating') -----
+ collect: aBlock
+ 	"Beware, the block will be evaluated only once per group of values."
+ 	^(self class runs: runs copy contents values: (values collect: aBlock)) coalesce!

Item was added:
+ ----- Method: RunArray>>copyUpThrough: (in category 'copying') -----
+ copyUpThrough: anElement
+ 	"Optimized"
+ 
+ 	| newValues |
+ 	newValues := values copyUpThrough: anElement.
+ 	^ self class
+ 		runs: (runs copyFrom: 1 to: newValues size)
+ 		values: newValues!

Item was added:
+ ----- Method: RunArray>>copyUpTo: (in category 'copying') -----
+ copyUpTo: anElement 
+ 	"Optimized"
+ 
+ 	| newValues |
+ 	newValues := values copyUpTo: anElement.
+ 	^ self class
+ 		runs: (runs copyFrom: 1 to: newValues size)
+ 		values: newValues!

Item was added:
+ ----- Method: RunArray>>copyUpToLast: (in category 'copying') -----
+ copyUpToLast: anElement
+ 	"Optimized"
+ 
+ 	| newValues |
+ 	newValues := values copyUpToLast: anElement.
+ 	^ self class
+ 		runs: (runs copyFrom: 1 to: newValues size)
+ 		values: newValues!

Item was added:
+ ----- Method: RunArray>>count: (in category 'enumerating') -----
+ count: aBlock
+ 	"Beware, the block will be evaluated only once per group of values."
+ 	| count |
+ 	count := 0.
+ 	self runsAndValuesDo: [:run :value |
+ 		(aBlock value: value)
+ 			ifTrue:
+ 				[count := count + run]].
+ 	^count!

Item was added:
+ ----- Method: RunArray>>detect:ifNone: (in category 'enumerating') -----
+ detect: aBlock ifNone: exceptionBlock 
+ 	"Only evaluate once per run"
+ 
+ 	^values detect: aBlock ifNone: exceptionBlock !

Item was added:
+ ----- Method: RunArray>>detectMax: (in category 'enumerating') -----
+ detectMax: aBlock
+ 	"Only evaluate once per run"
+ 
+ 	^values detectMax: aBlock!

Item was added:
+ ----- Method: RunArray>>detectMin: (in category 'enumerating') -----
+ detectMin: aBlock
+ 	"Only evaluate once per run"
+ 
+ 	^values detectMin: aBlock!

Item was added:
+ ----- Method: RunArray>>detectSum: (in category 'enumerating') -----
+ detectSum: aBlock
+ 	"Only loop on runs"
+ 	| sum |
+ 	sum := 0.
+ 	self runsAndValuesDo: [:run :value | 
+ 		sum := (aBlock value: value) * run + sum].  
+ 	^ sum!

Item was added:
+ ----- Method: RunArray>>do: (in category 'enumerating') -----
+ do: aBlock
+ 	"This is refined for speed"
+ 	
+ 	1 to: runs size do: [:i |
+ 		| r v |
+ 		v := values at: i.
+ 		r := runs at: i.
+ 		[( r := r - 1) >= 0]
+ 			whileTrue: [aBlock value: v]].!

Item was added:
+ ----- Method: RunArray>>fillFrom:with: (in category 'private') -----
+ fillFrom: aCollection with: aBlock
+ 	"Evaluate aBlock with each of aCollections's elements as the argument.  
+ 	Collect the resulting values into self. Answer self."
+ 
+ 	| newRuns newValues lastLength lastValue |
+ 	newRuns := (Array new: aCollection size) writeStream.
+ 	newValues := (Array new: aCollection size) writeStream.
+ 	lastLength := 0.
+ 	lastValue := Object new.
+ 	aCollection do: [:each | 
+ 		| value |
+ 		value := aBlock value: each.
+ 		lastValue = value
+ 			ifTrue: [lastLength := lastLength + 1]
+ 			ifFalse:
+ 				[lastLength > 0
+ 					ifTrue:
+ 						[newRuns nextPut: lastLength.
+ 						newValues nextPut: lastValue].
+ 				lastLength := 1.
+ 				lastValue := value]].
+ 	lastLength > 0
+ 		ifTrue:
+ 			[newRuns nextPut: lastLength.
+ 			newValues nextPut: lastValue].
+ 	self setRuns: newRuns contents setValues: newValues contents!

Item was added:
+ ----- Method: RunArray>>findFirst: (in category 'enumerating') -----
+ findFirst: aBlock
+ 	| index |
+ 	index := 1.
+ 	self runsAndValuesDo: [ :run :value |
+ 		(aBlock value: value) ifTrue: [^index].
+ 		index := index + run].
+ 	^0!

Item was added:
+ ----- Method: RunArray>>findLast: (in category 'enumerating') -----
+ findLast: aBlock
+ 	| index |
+ 	index := values size + 1.
+ 	[(index := index - 1) >= 1] whileTrue:
+ 		[(aBlock value: (values at: index)) ifTrue: [^(1 to: index) detectSum: [:i | runs at: i]]].
+ 	^0!

Item was added:
+ ----- Method: RunArray>>includes: (in category 'testing') -----
+ includes: anObject
+ 	"Answer whether anObject is one of the receiver's elements."
+ 
+ 	^values includes: anObject!

Item was added:
+ ----- Method: RunArray>>isSorted (in category 'testing') -----
+ isSorted
+ 	^values isSorted!

Item was added:
+ ----- Method: RunArray>>isSortedBy: (in category 'testing') -----
+ isSortedBy: aBlock
+ 	^values isSortedBy: aBlock!

Item was added:
+ ----- Method: RunArray>>noneSatisfy: (in category 'enumerating') -----
+ noneSatisfy: aBlock 
+ 	"Only evaluate once per run"
+ 
+ 	^values noneSatisfy: aBlock!

Item was added:
+ ----- Method: RunArray>>remove:ifAbsent: (in category 'removing') -----
+ remove: anObject ifAbsent: exceptionBlock
+ 	| index mustCoalesce run |
+ 	index := values indexOf: anObject ifAbsent: [^exceptionBlock value].
+ 	(run := runs at: index) > 1
+ 		ifTrue: [runs at: index put: run - 1]
+ 		ifFalse:
+ 			[mustCoalesce := index > 1 and: [index < values size and: [(values at: index - 1) = (values at: index + 1)]].
+ 			runs := runs copyWithoutIndex: index.
+ 			values := values copyWithoutIndex: index.
+ 			mustCoalesce
+ 				ifTrue:
+ 					[runs at: index - 1 put: (runs at: index - 1) + (runs at: index).
+ 					runs := runs copyWithoutIndex: index.
+ 					values := values copyWithoutIndex: index]].
+ 	^anObject!

Item was added:
+ ----- Method: RunArray>>removeAll (in category 'removing') -----
+ removeAll
+ 	runs := Array new.
+ 	values := Array new!

Item was added:
+ ----- Method: RunArray>>replace: (in category 'enumerating') -----
+ replace: aBlock
+ 	"Beware, the block will be evaluated only once per group of values."
+ 	values := values replace: aBlock.
+ 	self coalesce!

Item was added:
+ ----- Method: RunArray>>reverseDo: (in category 'enumerating') -----
+ reverseDo: aBlock
+ 	"This is refined for speed"
+ 	
+ 	| i |
+ 	i := runs size.
+ 	[i > 0]
+ 		whileTrue: 
+ 			[ | r v |
+ 			v := values at: i.
+ 			r := runs at: i.
+ 			i := i - 1.
+ 			[( r := r - 1) >= 0]
+ 				whileTrue: [aBlock value: v]].!

Item was added:
+ ----- Method: RunArray>>select: (in category 'enumerating') -----
+ select: aBlock
+ 	"Beware, the block will be evaluated only once per group of values."
+ 	| newRuns newValues |
+ 	newRuns := (Array new: runs size) writeStream.
+ 	newValues := (Array new: values size) writeStream.
+ 	self runsAndValuesDo: [:run :value |
+ 		(aBlock value: value)
+ 			ifTrue:
+ 				[newRuns add: run.
+ 				newValues add: value]].
+ 	^(self class runs: newRuns contents values: newValues contents) coalesce!




More information about the Squeak-dev mailing list