Hi,

here is a patch that boost a bit OrderedCollection,
I've added an array variable and change the code
in consequence. It's faster because it uses the special
bytecodes at: and at:put: that tries caches the primitive
calls

There is one regression with the simplex optimizer.

Cheers,
Gwen

From 1e260c9f24040ed9988480b90d697c4ce9437261 Mon Sep 17 00:00:00 2001
From: Gwenael Casaccio <[email protected]>
Date: Fri, 8 Nov 2013 10:06:52 +0100
Subject: [PATCH] Faster orderedcollection

---
 kernel/OrderColl.st                  | 122 +++++++++++++++++++----------------
 kernel/SortCollect.st                |  90 +++++++++++++-------------
 libgst/dict.c                        |   4 +-
 packages/stinst/parser/OrderedSet.st |  15 ++---
 tests/arrays.ok                      |   2 +-
 tests/stcompiler.ok                  |   4 +-
 6 files changed, 123 insertions(+), 114 deletions(-)

diff --git a/kernel/OrderColl.st b/kernel/OrderColl.st
index 9f0cf29..9f271d5 100644
--- a/kernel/OrderColl.st
+++ b/kernel/OrderColl.st
@@ -33,9 +33,8 @@
 
 
 SequenceableCollection subclass: OrderedCollection [
-    | firstIndex lastIndex |
+    | firstIndex lastIndex array |
     
-    <shape: #pointer>
     <category: 'Collections-Sequenceable'>
     <comment: 'My instances represent ordered collections of arbitrary typed objects which
 are not directly accessible by an index.  They can be accessed indirectly
@@ -46,7 +45,9 @@ on content (such as add:after:)'>
 	"Answer an OrderedCollection of size anInteger"
 
 	<category: 'instance creation'>
-	^(self basicNew: anInteger) initIndices
+	^self basicNew 
+            initialize: anInteger;
+            initIndices
     ]
 
     OrderedCollection class >> new [
@@ -56,6 +57,13 @@ on content (such as add:after:)'>
 	^self new: 16
     ]
 
+    copyEmpty [
+        "Answer an empty copy of the receiver"
+
+        <category: 'private'>
+        ^self copyEmpty: array size
+    ]
+
     do: aBlock [
         "Evaluate aBlock for all the elements in the collection"
 
@@ -63,7 +71,7 @@ on content (such as add:after:)'>
         | index |
         index := firstIndex.
         [ index <= lastIndex ] whileTrue: [
-            aBlock value: (self basicAt: index).
+            aBlock value: (array at: index).
             index := index + 1 ]
     ]
 
@@ -72,7 +80,7 @@ on content (such as add:after:)'>
 
 	<category: 'accessing'>
 	^lastIndex >= firstIndex
-	    ifTrue: [self basicAt: firstIndex]
+	    ifTrue: [array at: firstIndex]
 	    ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: 1]
     ]
 
@@ -81,7 +89,7 @@ on content (such as add:after:)'>
 
 	<category: 'accessing'>
 	^lastIndex >= firstIndex
-	    ifTrue: [self basicAt: lastIndex]
+	    ifTrue: [array at: lastIndex]
 	    ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: 0]
     ]
 
@@ -92,7 +100,7 @@ on content (such as add:after:)'>
 	| index |
 	index := anIndex + firstIndex - 1.
 	^(index >= firstIndex and: [index <= lastIndex]) 
-	    ifTrue: [self basicAt: index]
+	    ifTrue: [array at: index]
 	    ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex]
     ]
 
@@ -103,7 +111,7 @@ on content (such as add:after:)'>
 	| index |
 	index := anIndex + firstIndex - 1.
 	(index >= firstIndex and: [index <= lastIndex]) 
-	    ifTrue: [^self basicAt: index put: anObject]
+	    ifTrue: [^array at: index put: anObject]
 	    ifFalse: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex]
     ]
 
@@ -118,9 +126,9 @@ on content (such as add:after:)'>
 	"Add anObject in the receiver, answer it"
 
 	<category: 'adding'>
-	lastIndex == self basicSize ifTrue: [self growBy: self growSize shiftBy: 0].
+	lastIndex == array size ifTrue: [self growBy: self growSize shiftBy: 0].
 	lastIndex := lastIndex + 1.
-	^self basicAt: lastIndex put: anObject
+	^array at: lastIndex put: anObject
     ]
 
     add: newObject after: oldObject [
@@ -152,12 +160,12 @@ on content (such as add:after:)'>
 	(i between: 0 and: self size) 
 	    ifFalse: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: i].
 	index := i + firstIndex.
-	lastIndex == self basicSize ifTrue: [self growBy: self growSize shiftBy: 0].
+	lastIndex == array size ifTrue: [self growBy: self growSize shiftBy: 0].
 	lastIndex to: index
 	    by: -1
-	    do: [:i | self basicAt: i + 1 put: (self basicAt: i)].
+	    do: [:i | array at: i + 1 put: (array at: i)].
 	lastIndex := lastIndex + 1.
-	^self basicAt: index put: newObject
+	^array at: index put: newObject
     ]
 
     add: newObject beforeIndex: i [
@@ -178,7 +186,7 @@ on content (such as add:after:)'>
 	lastIndex := lastIndex + aCollection size.
 	aCollection do: 
 		[:element | 
-		self basicAt: index put: element.
+		array at: index put: element.
 		index := index + 1].
 	^aCollection
     ]
@@ -205,10 +213,10 @@ on content (such as add:after:)'>
 	self makeRoomLastFor: newCollection size.
 	lastIndex to: index
 	    by: -1
-	    do: [:i | self basicAt: i + newCollection size put: (self basicAt: i)].
+	    do: [:i | array at: i + newCollection size put: (array at: i)].
 	lastIndex := lastIndex + newCollection size.
 	(1 to: newCollection size) with: newCollection
-	    do: [:i :each | self basicAt: index + i - 1 put: each].
+	    do: [:i :each | array at: index + i - 1 put: each].
 	^newCollection
     ]
 
@@ -240,7 +248,7 @@ on content (such as add:after:)'>
 	index := firstIndex := firstIndex - aCollection size.
 	aCollection do: 
 		[:element | 
-		self basicAt: index put: element.
+		array at: index put: element.
 		index := index + 1].
 	^aCollection
     ]
@@ -256,7 +264,7 @@ on content (such as add:after:)'>
 	lastIndex := lastIndex + aCollection size.
 	aCollection do: 
 		[:element | 
-		self basicAt: index put: element.
+		array at: index put: element.
 		index := index + 1].
 	^aCollection
     ]
@@ -268,7 +276,7 @@ on content (such as add:after:)'>
 	<category: 'adding'>
 	firstIndex <= 1 ifTrue: [self growBy: self growSize shiftBy: self growSize].
 	firstIndex := firstIndex - 1.
-	^self basicAt: firstIndex put: newObject
+	^array at: firstIndex put: newObject
     ]
 
     addLast: newObject [
@@ -276,9 +284,9 @@ on content (such as add:after:)'>
 	 Answer newObject"
 
 	<category: 'adding'>
-	lastIndex == self basicSize ifTrue: [self growBy: self growSize shiftBy: 0].
+	lastIndex == array size ifTrue: [self growBy: self growSize shiftBy: 0].
 	lastIndex := lastIndex + 1.
-	^self basicAt: lastIndex put: newObject
+	^array at: lastIndex put: newObject
     ]
 
     removeFirst [
@@ -289,8 +297,8 @@ on content (such as add:after:)'>
 	| answer |
 	lastIndex < firstIndex 
 	    ifTrue: [^SystemExceptions.EmptyCollection signalOn: self].
-	answer := self basicAt: firstIndex.	"Get the element"
-	self basicAt: firstIndex put: nil.	"Allow it to be garbage collected"
+	answer := array at: firstIndex.	"Get the element"
+	array at: firstIndex put: nil.	"Allow it to be garbage collected"
 	lastIndex = firstIndex 
 	    ifTrue: [self initIndices]
 	    ifFalse: [firstIndex := firstIndex + 1].
@@ -306,8 +314,8 @@ on content (such as add:after:)'>
 	| answer |
 	lastIndex < firstIndex 
 	    ifTrue: [^SystemExceptions.EmptyCollection signalOn: self].
-	answer := self basicAt: lastIndex.	"Get the element"
-	self basicAt: lastIndex put: nil.	"Allow it to be garbage collected"
+	answer := array at: lastIndex.	"Get the element"
+	array at: lastIndex put: nil.	"Allow it to be garbage collected"
 	lastIndex = firstIndex 
 	    ifTrue: [self initIndices]
 	    ifFalse: [lastIndex := lastIndex - 1].
@@ -367,10 +375,10 @@ on content (such as add:after:)'>
 	    ifTrue: [^SystemExceptions.EmptyCollection signalOn: self].
 	(anIndex < 1 or: [anIndex > self size]) 
 	    ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex].
-	answer := self basicAt: anIndex + firstIndex - 1.
-        self primReplaceFrom: anIndex + firstIndex - 1 to: lastIndex - 1
-            with: self startingAt: anIndex + firstIndex.
-	self basicAt: lastIndex put: nil.
+	answer := array at: anIndex + firstIndex - 1.
+        array replaceFrom: anIndex + firstIndex - 1 to: lastIndex - 1
+            with: array startingAt: anIndex + firstIndex.
+	array at: lastIndex put: nil.
 	lastIndex = firstIndex 
 	    ifTrue: [self initIndices]
 	    ifFalse: [lastIndex := lastIndex - 1].
@@ -382,9 +390,9 @@ on content (such as add:after:)'>
 	 Don't override this method!"
 
 	<category: 'private methods'>
-	lastIndex == self basicSize ifTrue: [self growBy: self growSize shiftBy: 0].
+	lastIndex == array size ifTrue: [self growBy: self growSize shiftBy: 0].
 	lastIndex := lastIndex + 1.
-	^self basicAt: lastIndex put: newObject
+	^array at: lastIndex put: newObject
     ]
 
     basicAddAllLast: aCollection [
@@ -398,7 +406,7 @@ on content (such as add:after:)'>
 	lastIndex := lastIndex + aCollection size.
 	aCollection do: 
 		[:element | 
-		self basicAt: index put: element.
+		array at: index put: element.
 		index := index + 1].
 	^aCollection
     ]
@@ -411,8 +419,8 @@ on content (such as add:after:)'>
 	| answer |
 	lastIndex < firstIndex 
 	    ifTrue: [^SystemExceptions.EmptyCollection signalOn: self].
-	answer := self basicAt: firstIndex.	"Get the element"
-	self basicAt: firstIndex put: nil.	"Allow it to be garbage collected"
+	answer := array at: firstIndex.	"Get the element"
+	array at: firstIndex put: nil.	"Allow it to be garbage collected"
 	lastIndex = firstIndex 
 	    ifTrue: [self initIndices]
 	    ifFalse: [firstIndex := firstIndex + 1].
@@ -428,8 +436,8 @@ on content (such as add:after:)'>
 	| answer |
 	lastIndex < firstIndex 
 	    ifTrue: [^SystemExceptions.EmptyCollection signalOn: self].
-	answer := self basicAt: lastIndex.	"Get the element"
-	self basicAt: lastIndex put: nil.	"Allow it to be garbage collected"
+	answer := array at: lastIndex.	"Get the element"
+	array at: lastIndex put: nil.	"Allow it to be garbage collected"
 	lastIndex = firstIndex 
 	    ifTrue: [self initIndices]
 	    ifFalse: [lastIndex := lastIndex - 1].
@@ -437,9 +445,14 @@ on content (such as add:after:)'>
 	^answer
     ]
 
+    initialize: anInteger [
+	<category: 'private methods'>
+        array := Array new: anInteger
+    ]
+
     initIndices [
 	<category: 'private methods'>
-	firstIndex := self basicSize // 2 max: 1.
+	firstIndex := array size // 2 max: 1.
 	lastIndex := firstIndex - 1
     ]
 
@@ -449,6 +462,13 @@ on content (such as add:after:)'>
 	lastIndex := last
     ]
 
+    postCopy [
+        <category: 'copying'>
+
+        array := array copy.
+        super postCopy.
+    ]
+
     makeRoomFirstFor: n [
 	"Private - Make room for n elements at the start of the collection"
 
@@ -461,13 +481,13 @@ on content (such as add:after:)'>
 	"Private - Make room for n elements at the end of the collection"
 
 	<category: 'private methods'>
-	lastIndex + n > self basicSize 
+	lastIndex + n > array size 
 	    ifTrue: [self growBy: (n max: self growSize) shiftBy: 0]
     ]
 
     shrinkSize [
 	<category: 'private methods'>
-	^self basicSize // 3
+	^array size // 3
     ]
 
     shrink [
@@ -481,7 +501,7 @@ on content (such as add:after:)'>
 	shift := firstIndex - 1 min: shrink // 2.
 
 	"Check that the new lastIndex is <= basicSize."
-	shrink := shrink min: self basicSize - (lastIndex - shift).
+	shrink := shrink min: array size - (lastIndex - shift).
 	self growBy: shrink negated shiftBy: shift negated
     ]
 
@@ -499,24 +519,14 @@ on content (such as add:after:)'>
 
 	<category: 'private methods'>
 	| newOrderedCollection |
-	newOrderedCollection := self copyEmpty: self basicSize + delta.
+	newOrderedCollection := array copyEmpty: array size + delta.
         newOrderedCollection
-            primReplaceFrom: firstIndex + shiftCount to: lastIndex + shiftCount
-            with: self startingAt: firstIndex.
-	newOrderedCollection firstIndex: firstIndex + shiftCount
+            replaceFrom: firstIndex + shiftCount to: lastIndex + shiftCount
+            with: array startingAt: firstIndex.
+	self
+            firstIndex: firstIndex + shiftCount
 	    lastIndex: lastIndex + shiftCount.
-	self become: newOrderedCollection
-    ]
-
-    primReplaceFrom: start to: stop with: byteArray startingAt: replaceStart [
-        "Replace the characters from start to stop with new characters whose
-         ASCII codes are contained in byteArray, starting at the replaceStart
-         location of byteArray"
-
-        <category: 'built ins'>
-        <primitive: VMpr_ArrayedCollection_replaceFromToWithStartingAt>
-        self primitiveFailed
+	array := newOrderedCollection
     ]
-
 ]
 
diff --git a/kernel/SortCollect.st b/kernel/SortCollect.st
index ef8a8bc..a7b88b3 100644
--- a/kernel/SortCollect.st
+++ b/kernel/SortCollect.st
@@ -136,8 +136,8 @@ above criteria -- actually any object which responds to #value:value:.'>
 	lastOrdered = lastIndex 
 	    ifFalse: [sorted ifTrue: [self merge] ifFalse: [self makeHeap]].
 	^sorted 
-	    ifTrue: [self basicAt: lastIndex]
-	    ifFalse: [self basicAt: firstIndex]
+	    ifTrue: [array at: lastIndex]
+	    ifFalse: [array at: firstIndex]
     ]
 
     at: anIndex [
@@ -268,7 +268,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 		    high: lastIndex.
 	i isNil ifTrue: [^aBlock value].
 	j := i - firstIndex + 1.
-	[j ~= index and: [(self basicAt: i - 1) = anObject]] whileTrue: 
+	[j ~= index and: [(array at: i - 1) = anObject]] whileTrue: 
 		[i := i - 1.
 		j := j - 1].
 	^j
@@ -347,7 +347,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 	 collect: method."
 
 	<category: 'private methods'>
-	^OrderedCollection new: self basicSize
+	^OrderedCollection new: array size
     ]
 
     initIndices [
@@ -362,7 +362,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 	"Private - Make room for n elements at the end of the collection"
 
 	<category: 'private methods'>
-	lastIndex + n > self basicSize 
+	lastIndex + n > array size 
 	    ifTrue: [self growBy: (n max: self growSize) shiftBy: 1 - firstIndex]
     ]
 
@@ -386,15 +386,15 @@ above criteria -- actually any object which responds to #value:value:.'>
 
 		parentIndex := start.
 		childIndex := parentIndex + parentIndex.
-		parent := self basicAt: delta + parentIndex.
+		parent := array at: delta + parentIndex.
 		
 		[childIndex > heapSize or: 
 			["Pick the greatest of the two children"
 
-			child := self basicAt: delta + childIndex.
+			child := array at: delta + childIndex.
 			childIndex = heapSize 
 			    ifFalse: 
-				[childB := self basicAt: delta + childIndex + 1.
+				[childB := array at: delta + childIndex + 1.
 				(self sortBlock value: child value: childB) 
 				    ifTrue: 
 					[child := childB.
@@ -404,8 +404,8 @@ above criteria -- actually any object which responds to #value:value:.'>
 			    ["The parent is less than the child -- so the child is actually
 			     meant to be the parent."
 
-			    self basicAt: delta + childIndex put: parent.
-			    self basicAt: delta + parentIndex put: child.
+			    array at: delta + childIndex put: parent.
+			    array at: delta + parentIndex put: child.
 			    parentIndex := childIndex.
 			    childIndex := childIndex + childIndex]]
     ]
@@ -445,16 +445,16 @@ above criteria -- actually any object which responds to #value:value:.'>
 	| holeIndex parentIndex parent item |
 	lastOrdered := lastOrdered + 1.
 	holeIndex := lastOrdered - firstIndex.
-	item := self basicAt: lastOrdered.
+	item := array at: lastOrdered.
 	
 	[holeIndex > 0 and: 
 		[parentIndex := (holeIndex - 1) // 2.
-		sortBlock value: (parent := self basicAt: firstIndex + parentIndex)
+		sortBlock value: (parent := array at: firstIndex + parentIndex)
 		    value: item]] 
 		whileTrue: 
-		    [self basicAt: firstIndex + holeIndex put: parent.
+		    [array at: firstIndex + holeIndex put: parent.
 		    holeIndex := parentIndex].
-	self basicAt: firstIndex + holeIndex put: item
+	array at: firstIndex + holeIndex put: item
     ]
 
     percolateDown [
@@ -474,15 +474,15 @@ above criteria -- actually any object which responds to #value:value:.'>
 	childIndex := 2.
 	delta := firstIndex - 1.
 	heapSize := lastOrdered - delta.
-	parent := self basicAt: delta + parentIndex.
+	parent := array at: delta + parentIndex.
 	
 	[childIndex > heapSize ifTrue: [^self].
 
 	"Pick the greatest of the two children"
-	child := self basicAt: delta + childIndex.
+	child := array at: delta + childIndex.
 	childIndex = heapSize 
 	    ifFalse: 
-		[childB := self basicAt: delta + childIndex + 1.
+		[childB := array at: delta + childIndex + 1.
 		(self sortBlock value: child value: childB) 
 		    ifTrue: 
 			[child := childB.
@@ -492,8 +492,8 @@ above criteria -- actually any object which responds to #value:value:.'>
 		    ["The parent is less than the child -- so the child is actually
 		     meant to be the parent."
 
-		    self basicAt: delta + childIndex put: parent.
-		    self basicAt: delta + parentIndex put: child.
+		    array at: delta + childIndex put: parent.
+		    array at: delta + parentIndex put: child.
 		    parentIndex := childIndex.
 		    childIndex := childIndex + childIndex]
     ]
@@ -524,21 +524,21 @@ above criteria -- actually any object which responds to #value:value:.'>
     basicSwap: indexA ifBefore: indexB [
 	<category: 'private methods - sorting'>
 	| a b |
-	(sortBlock value: (a := self basicAt: indexA)
-	    value: (b := self basicAt: indexB)) 
+	(sortBlock value: (a := array at: indexA)
+	    value: (b := array at: indexB)) 
 		ifTrue: 
-		    [self basicAt: indexA put: b.
-		    self basicAt: indexB put: a]
+		    [array at: indexA put: b.
+		    array at: indexB put: a]
     ]
 
     basicSwap: indexA ifAfter: indexB [
 	<category: 'private methods - sorting'>
 	| a b |
-	(sortBlock value: (a := self basicAt: indexA)
-	    value: (b := self basicAt: indexB)) 
+	(sortBlock value: (a := array at: indexA)
+	    value: (b := array at: indexB)) 
 		ifFalse: 
-		    [self basicAt: indexA put: b.
-		    self basicAt: indexB put: a]
+		    [array at: indexA put: b.
+		    array at: indexB put: a]
     ]
 
     basicSwap: anIndex with: anotherIndex [
@@ -547,9 +547,9 @@ above criteria -- actually any object which responds to #value:value:.'>
 
 	<category: 'private methods - sorting'>
 	| saved |
-	saved := self basicAt: anIndex.
-	self basicAt: anIndex put: (self basicAt: anotherIndex).
-	self basicAt: anotherIndex put: saved
+	saved := array at: anIndex.
+	array at: anIndex put: (array at: anotherIndex).
+	array at: anotherIndex put: saved
     ]
 
     merge [
@@ -560,7 +560,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 	| i add aCollection delta |
 	self sortFrom: lastOrdered + 1 to: lastIndex.
 	aCollection := (lastOrdered + 1 to: lastIndex) 
-		    collect: [:each | self basicAt: each].
+		    collect: [:each | array at: each].
 
 	"Merge elements into the collection. We do binary searches on the
 	 not yet sorted part of the collection to find where to add the
@@ -571,10 +571,10 @@ above criteria -- actually any object which responds to #value:value:.'>
 		[:element | 
 		| newIndex |
 		newIndex := self insertionIndexFor: element upTo: i.
-                self primReplaceFrom: newIndex + add to: i + add
-                    with: self startingAt: newIndex.
+                array replaceFrom: newIndex + add to: i + add
+                    with: array startingAt: newIndex.
 		add := add - 1.
-		self basicAt: newIndex + add put: element.
+		array at: newIndex + add put: element.
                 i := newIndex - 1].
 	lastOrdered := lastIndex.
 	sorted := true.
@@ -587,9 +587,9 @@ above criteria -- actually any object which responds to #value:value:.'>
 
 	<category: 'private methods - sorting'>
 	| a b c |
-	a := self basicAt: ia.
-	b := self basicAt: ib.
-	c := self basicAt: ic.
+	a := array at: ia.
+	b := array at: ib.
+	c := array at: ic.
 	(sortBlock value: a value: b) 
 	    ifTrue: 
 		[(sortBlock value: b value: c) ifTrue: [^ib].
@@ -620,7 +620,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 	self basicSwap: first ifAfter: mid.
 	self basicSwap: mid ifAfter: last.
 	self basicSwap: first ifAfter: last.
-	pivot := self basicAt: mid.
+	pivot := array at: mid.
 	smaller := first.
 	larger := last.
 	
@@ -628,13 +628,13 @@ above criteria -- actually any object which responds to #value:value:.'>
 	[smaller <= last and: 
 		["self[smaller] <= pivot"
 
-		sortBlock value: (self basicAt: smaller) value: pivot]] 
+		sortBlock value: (array at: smaller) value: pivot]] 
 		whileTrue: [smaller := smaller + 1].
 	
 	[larger >= first and: 
 		["self[larger] >= pivot"
 
-		sortBlock value: pivot value: (self basicAt: larger)]] 
+		sortBlock value: pivot value: (array at: larger)]] 
 		whileTrue: [larger := larger - 1].
 	smaller < larger] 
 		whileTrue: 
@@ -685,7 +685,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 	
 	[i > j ifTrue: [^nil].
 	mid := (i + j + 1) // 2.
-	element := self basicAt: mid.
+	element := array at: mid.
 	compare := self compare: anObject with: element.
 	compare = 0] 
 		whileFalse: [compare < 0 ifTrue: [j := mid - 1] ifFalse: [i := mid + 1]].
@@ -697,7 +697,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 	    by: -1
 	    do: 
 		[:goDown | 
-		element := self basicAt: goDown.
+		element := array at: goDown.
 		(self compare: anObject with: element) = 0 
 		    ifFalse: 
 			["Exhausted the sort-block-equal elements in this direction,
@@ -706,7 +706,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 			mid to: high
 			    do: 
 				[:goUp | 
-				element := self basicAt: goUp.
+				element := array at: goUp.
 				(self compare: anObject with: element) = 0 ifFalse: [^nil].
 
 				"Another sort-block equal element to test against."
@@ -721,7 +721,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 	mid to: high
 	    do: 
 		[:goUp | 
-		element := self basicAt: goUp.
+		element := array at: goUp.
 		(self compare: anObject with: element) = 0 ifFalse: [^nil].
 
 		"Another sort-block equal element to test against."
@@ -741,7 +741,7 @@ above criteria -- actually any object which responds to #value:value:.'>
 	
 	[mid := (high + low) // 2.
 	low > high] whileFalse: 
-		    [(sortBlock value: (self basicAt: mid) value: anObject) 
+		    [(sortBlock value: (array at: mid) value: anObject) 
 			ifTrue: [low := mid + 1]
 			ifFalse: [high := mid - 1]].
 	^low
diff --git a/libgst/dict.c b/libgst/dict.c
index 0b4ddb9..3285ef7 100644
--- a/libgst/dict.c
+++ b/libgst/dict.c
@@ -521,8 +521,8 @@ static const class_definition class_info[] = {
    "Interval", "start stop step", NULL, NULL },
 
   {&_gst_ordered_collection_class, &_gst_sequenceable_collection_class,
-   GST_ISP_POINTER, false, 2,
-   "OrderedCollection", "firstIndex lastIndex", NULL, NULL },
+   GST_ISP_FIXED, false, 3,
+   "OrderedCollection", "firstIndex lastIndex array", NULL, NULL },
 
   {&_gst_sorted_collection_class, &_gst_ordered_collection_class,
    GST_ISP_POINTER, false, 3,
diff --git a/packages/stinst/parser/OrderedSet.st b/packages/stinst/parser/OrderedSet.st
index fe00345..3a00131 100644
--- a/packages/stinst/parser/OrderedSet.st
+++ b/packages/stinst/parser/OrderedSet.st
@@ -34,7 +34,6 @@
 OrderedCollection subclass: OrderedSet [
     | unorderedSet |
     
-    <shape: #pointer>
     <category: 'Collections-Sequenceable'>
     <comment: 'My instances represent sets of unique objects that may be accessed by
 an arbitrary index.  Besides allowing addition, removal, and insertion
@@ -189,14 +188,14 @@ already present.'>
 	self makeRoomLastFor: newCollection size.
 	lastIndex to: index
 	    by: -1
-	    do: [:i | self basicAt: i + newCollection size put: (self basicAt: i)].
+	    do: [:i | array at: i + newCollection size put: (array at: i)].
 	lastIndex := lastIndex + newCollection size.
 	newCollection do: 
 		[:each | 
 		(unorderedSet includes: each) 
 		    ifFalse: 
 			[unorderedSet add: each.
-			self basicAt: index put: each.
+			array at: index put: each.
 			index := 1 + index]].
 	self closeGapFrom: index - firstIndex + 1 to: i + newCollection size.
 	^newCollection
@@ -214,7 +213,7 @@ already present.'>
 		[:elt | 
 		(unorderedSet includes: elt) 
 		    ifFalse: 
-			[self basicAt: index put: elt.
+			[array at: index put: elt.
 			unorderedSet add: elt.
 			index := index + 1]].
 	self closeGapFrom: index - firstIndex + 1 to: aCollection size.
@@ -235,7 +234,7 @@ already present.'>
 		(unorderedSet includes: element) 
 		    ifFalse: 
 			[lastIndex := lastIndex + 1.
-			self basicAt: lastIndex put: element.
+			array at: lastIndex put: element.
 			unorderedSet add: element]].
 	^aCollection
     ]
@@ -318,7 +317,7 @@ already present.'>
 	gapStart - 1 < (lastIndex - realEnd) 
 	    ifTrue: 
 		[
-		[self basicAt: realEnd put: (self basicAt: (realStart := realStart - 1)).
+		[array at: realEnd put: (array at: (realStart := realStart - 1)).
 		realEnd := realEnd - 1.
 		realStart = firstIndex] 
 			whileFalse.
@@ -327,13 +326,13 @@ already present.'>
 		["shift from after"
 
 		
-		[self basicAt: realStart put: (self basicAt: (realEnd := realEnd + 1)).
+		[array at: realStart put: (array at: (realEnd := realEnd + 1)).
 		realStart := realStart + 1.
 		realEnd = lastIndex] 
 			whileFalse.
 		lastIndex := realStart - 1].
 	"help the gc"
-	realStart to: realEnd do: [:i | self basicAt: i put: nil]
+	realStart to: realEnd do: [:i | array at: i put: nil]
     ]
 
     growBy: delta shiftBy: shiftCount [
diff --git a/tests/arrays.ok b/tests/arrays.ok
index 989e882..6149d47 100644
--- a/tests/arrays.ok
+++ b/tests/arrays.ok
@@ -99,7 +99,7 @@ returned value is '(() )'
 
 Execution begins...
 SortedCollection (8->1 12->1 4->2 7->2 5->3 6->3 9->8 )
-returned value is SortedCollection new: 10 "<0>"
+returned value is SortedCollection new: 0 "<0>"
 
 Execution begins...
 (1 1 2 3 5 )
diff --git a/tests/stcompiler.ok b/tests/stcompiler.ok
index ee3769e..11ad56c 100644
--- a/tests/stcompiler.ok
+++ b/tests/stcompiler.ok
@@ -43,10 +43,10 @@ and block temporaries too!
 returned value is TextCollector new "<0>"
 
 Execution begins...
-returned value is OrderedSet new: 32 "<0>"
+returned value is OrderedSet new "<0>"
 
 Execution begins...
-returned value is OrderedSet new: 32 "<0>"
+returned value is OrderedSet new "<0>"
 
 Execution begins...
 returned value is 'an'
-- 
1.8.3.2

_______________________________________________
help-smalltalk mailing list
[email protected]
https://lists.gnu.org/mailman/listinfo/help-smalltalk

Reply via email to