瀏覽代碼

Merge pull request #388 from herby/indexable-collection

Indexable collection
Nicolas Petton 12 年之前
父節點
當前提交
2d80f29a84
共有 7 個文件被更改,包括 1687 次插入1132 次删除
  1. 332 135
      js/Kernel-Collections.deploy.js
  2. 352 139
      js/Kernel-Collections.js
  3. 458 386
      js/Kernel-Tests.deploy.js
  4. 433 433
      js/Kernel-Tests.js
  5. 2 1
      js/boot.js
  6. 99 36
      st/Kernel-Collections.st
  7. 11 2
      st/Kernel-Tests.st

文件差異過大導致無法顯示
+ 332 - 135
js/Kernel-Collections.deploy.js


文件差異過大導致無法顯示
+ 352 - 139
js/Kernel-Collections.js


文件差異過大導致無法顯示
+ 458 - 386
js/Kernel-Tests.deploy.js


文件差異過大導致無法顯示
+ 433 - 433
js/Kernel-Tests.js


+ 2 - 1
js/boot.js

@@ -822,7 +822,8 @@ smalltalk.wrapClassName("Date", "Kernel", Date, smalltalk.Object);
 smalltalk.wrapClassName("UndefinedObject", "Kernel", SmalltalkNil, smalltalk.Object, false);
 smalltalk.wrapClassName("UndefinedObject", "Kernel", SmalltalkNil, smalltalk.Object, false);
 
 
 smalltalk.addClass("Collection", smalltalk.Object, null, "Kernel");
 smalltalk.addClass("Collection", smalltalk.Object, null, "Kernel");
-smalltalk.addClass("SequenceableCollection", smalltalk.Collection, null, "Kernel");
+smalltalk.addClass("IndexableCollection", smalltalk.Collection, null, "Kernel");
+smalltalk.addClass("SequenceableCollection", smalltalk.IndexableCollection, null, "Kernel");
 smalltalk.addClass("CharacterArray", smalltalk.SequenceableCollection, null, "Kernel");
 smalltalk.addClass("CharacterArray", smalltalk.SequenceableCollection, null, "Kernel");
 smalltalk.wrapClassName("String", "Kernel", String, smalltalk.CharacterArray);
 smalltalk.wrapClassName("String", "Kernel", String, smalltalk.CharacterArray);
 smalltalk.wrapClassName("Symbol", "Kernel", SmalltalkSymbol, smalltalk.CharacterArray, false);
 smalltalk.wrapClassName("Symbol", "Kernel", SmalltalkSymbol, smalltalk.CharacterArray, false);

+ 99 - 36
st/Kernel-Collections.st

@@ -302,7 +302,88 @@ withAll: aCollection
 		yourself
 		yourself
 ! !
 ! !
 
 
-Collection subclass: #HashedCollection
+Collection subclass: #IndexableCollection
+	instanceVariableNames: ''
+	package: 'Kernel-Collections'!
+!IndexableCollection commentStamp!
+An IndexableCollection is a key-value store, that is,
+it stores values under indexes.
+
+As a rule of thumb, if a collection has at: and at:put:,
+it is an IndexableCollection.!
+
+!IndexableCollection methodsFor: 'accessing'!
+
+at: anIndex
+	"Lookup the given index in the receiver. 
+	If it is present, answer the value stored at anIndex. 
+	Otherwise, raise an error."
+
+	^self at: anIndex ifAbsent: [ self errorNotFound ]
+!
+
+at: anIndex ifAbsent: aBlock
+	"Lookup the given index in the receiver. 
+	If it is present, answer the value stored at anIndex. 
+	Otherwise, answer the value of aBlock."
+
+	self subclassReponsibility
+!
+
+at: anIndex ifPresent: aBlock
+	"Lookup the given index in the receiver. 
+	If it is present, answer the value of evaluating aBlock with the value stored at anIndex. 
+	Otherwise, answer nil."
+
+	^self at: anIndex ifPresent: aBlock ifAbsent: [ nil ]
+!
+
+at: anIndex ifPresent: aBlock ifAbsent: anotherBlock
+	"Lookup the given index in the receiver. 
+	If it is present, answer the value of evaluating aBlock with the value stored at anIndex.
+	Otherwise, answer the value of anotherBlock."
+
+	self subclassReponsibility
+!
+
+at: anIndex put: anObject
+	"Store anObject under the given index in the receiver."
+
+	self subclassReponsibility
+!
+
+indexOf: anObject
+	"Lookup index at which anObject is stored in the receiver.
+	If not present, raise an error."
+
+	^self indexOf: anObject ifAbsent: [ self errorNotFound ]
+!
+
+indexOf: anObject ifAbsent: aBlock
+	"Lookup index at which anObject is stored in the receiver.
+	If not present, return value of executing aBlock."
+
+	self subclassResponsibility
+! !
+
+!IndexableCollection methodsFor: 'enumeration'!
+
+with: anotherCollection do: aBlock
+	"Calls aBlock with every value from self
+	and with indetically-indexed value from anotherCollection"
+
+	self withIndexDo: [ :each :index |
+		aBlock value: each value: (anotherCollection at: index) ]
+!
+
+withIndexDo: aBlock
+	"Calls aBlock with every value from self
+	and with its index as the second argument"
+
+	self subclassReponsibility
+! !
+
+IndexableCollection subclass: #HashedCollection
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	package: 'Kernel-Collections'!
 	package: 'Kernel-Collections'!
 !HashedCollection commentStamp!
 !HashedCollection commentStamp!
@@ -319,10 +400,6 @@ associations
 	^associations
 	^associations
 !
 !
 
 
-at: aKey
-	^self at: aKey ifAbsent: [self errorNotFound]
-!
-
 at: aKey ifAbsent: aBlock
 at: aKey ifAbsent: aBlock
 	^(self includesKey: aKey)
 	^(self includesKey: aKey)
 		ifTrue: [self basicAt: aKey]
 		ifTrue: [self basicAt: aKey]
@@ -334,15 +411,6 @@ at: aKey ifAbsentPut: aBlock
 	    self at: aKey put: aBlock value]
 	    self at: aKey put: aBlock value]
 !
 !
 
 
-at: aKey ifPresent: aBlock
-	"Lookup the given key in the receiver. 
-	If it is present, answer the value of evaluating the given block with the value associated with the key. 
-	Otherwise, answer nil."
-	^(self includesKey: aKey)
-		ifTrue: [ aBlock value: (self at: aKey) ]
-		ifFalse: [ nil ]
-!
-
 at: aKey ifPresent: aBlock ifAbsent: anotherBlock
 at: aKey ifPresent: aBlock ifAbsent: anotherBlock
 	"Lookup the given key in the receiver. 
 	"Lookup the given key in the receiver. 
 	If it is present, answer the value of evaluating the oneArgBlock with the value associated with the key, 
 	If it is present, answer the value of evaluating the oneArgBlock with the value associated with the key, 
@@ -356,6 +424,11 @@ at: aKey put: aValue
 	^self basicAt: aKey put: aValue
 	^self basicAt: aKey put: aValue
 !
 !
 
 
+indexOf: anObject ifAbsent: aBlock
+
+	^ self keys detect: [ :each | (self at: each) = anObject ] ifNone: aBlock
+!
+
 keys
 keys
 	<
 	<
 		if ('function'===typeof Object.keys) return Object.keys(self);
 		if ('function'===typeof Object.keys) return Object.keys(self);
@@ -492,6 +565,10 @@ select: aBlock
 
 
 valuesDo: aBlock
 valuesDo: aBlock
 	self keysAndValuesDo: [ :key :value | aBlock value: value ]
 	self keysAndValuesDo: [ :key :value | aBlock value: value ]
+!
+
+withIndexDo: aBlock
+	self keysAndValuesDo: [ :key :value | aBlock value: value value: key ]
 ! !
 ! !
 
 
 !HashedCollection methodsFor: 'printing'!
 !HashedCollection methodsFor: 'printing'!
@@ -555,11 +632,11 @@ at: aKey put: aValue
 	>
 	>
 !
 !
 
 
-keyAtValue: anObject
+indexOf: anObject ifAbsent: aBlock
 
 
-	^ (self associations 
-    	detect:[:k :v| v == anObject] 
-    	ifNone:[self error: 'Not found']) key
+	| index |
+    index := values indexOf: anObject ifAbsent: [0].
+    ^ index = 0 ifTrue: [ aBlock value ] ifFalse: [ keys at: index ]
 !
 !
 
 
 keys
 keys
@@ -639,9 +716,12 @@ includesKey: aKey
 	< return self._positionOfKey_(aKey) >>= 0; >
 	< return self._positionOfKey_(aKey) >>= 0; >
 ! !
 ! !
 
 
-Collection subclass: #SequenceableCollection
+IndexableCollection subclass: #SequenceableCollection
 	instanceVariableNames: ''
 	instanceVariableNames: ''
 	package: 'Kernel-Collections'!
 	package: 'Kernel-Collections'!
+!SequenceableCollection commentStamp!
+A SequencableCollection is an IndexableCollection
+with numeric indexes starting with 1.!
 
 
 !SequenceableCollection methodsFor: 'accessing'!
 !SequenceableCollection methodsFor: 'accessing'!
 
 
@@ -653,19 +733,6 @@ allButLast
 	^self copyFrom: 1 to: self size - 1
 	^self copyFrom: 1 to: self size - 1
 !
 !
 
 
-at: anIndex
-	^self at: anIndex ifAbsent: [
-	    self errorNotFound]
-!
-
-at: anIndex ifAbsent: aBlock
-	self subclassResponsibility
-!
-
-at: anIndex put: anObject
-	self subclassResponsibility
-!
-
 atRandom
 atRandom
 	^ self at: self size atRandom
 	^ self at: self size atRandom
 !
 !
@@ -685,10 +752,6 @@ fourth
 	^self at: 4
 	^self at: 4
 !
 !
 
 
-indexOf: anObject
-	^self indexOf: anObject ifAbsent: [self errorNotFound]
-!
-
 indexOf: anObject ifAbsent: aBlock
 indexOf: anObject ifAbsent: aBlock
 	<
 	<
 		for(var i=0;i<self.length;i++) {
 		for(var i=0;i<self.length;i++) {

+ 11 - 2
st/Kernel-Tests.st

@@ -428,11 +428,20 @@ CollectionTest subclass: #HashedCollectionTest
 !HashedCollectionTest methodsFor: 'accessing'!
 !HashedCollectionTest methodsFor: 'accessing'!
 
 
 collection
 collection
-	^ #{ 'a' -> 1. 'b' -> 2. 'c' -> 3. 'd' -> -4 }
+	^ #{ 'b' -> 1. 'a' -> 2. 'c' -> 3. 'd' -> -4 }
 !
 !
 
 
 collectionWithDuplicates
 collectionWithDuplicates
-	^ #{ 'a' -> 1. 'b' -> 2. 'c' -> 3. 'd' -> -4. 'e' -> 1. 'f' -> 2. 'g' -> 10 }
+	^ #{ 'b' -> 1. 'a' -> 2. 'c' -> 3. 'd' -> -4. 'e' -> 1. 'f' -> 2. 'g' -> 10 }
+! !
+
+!HashedCollectionTest methodsFor: 'tests'!
+
+testIndexOf
+
+	self assert: (self collection indexOf: 2) equals: 'a'.
+	self should: [ self collection indexOf: 999 ] raise: Error.
+	self assert: (self collection indexOf: 999 ifAbsent: [ 'sentinel' ]) equals: 'sentinel'
 ! !
 ! !
 
 
 !HashedCollectionTest class methodsFor: 'accessing'!
 !HashedCollectionTest class methodsFor: 'accessing'!

部分文件因文件數量過多而無法顯示