Browse Source

More tests and fixes for collections

Nicolas Petton 12 years ago
parent
commit
291eeaa7bb

+ 73 - 5
js/Kernel-Collections.deploy.js

@@ -166,10 +166,10 @@ smalltalk.method({
 selector: "collect:",
 fn: function (aBlock) {
 var self=this;
-var newCollection=nil;
-(newCollection=smalltalk.send(smalltalk.send(self, "_class", []), "_new", []));
-smalltalk.send(self, "_do_", [(function(each){return smalltalk.send(newCollection, "_add_", [smalltalk.send(aBlock, "_value_", [each])]);})]);
-return newCollection;
+var stream=nil;
+(stream=smalltalk.send(smalltalk.send(smalltalk.send(self, "_class", []), "_new", []), "_writeStream", []));
+smalltalk.send(self, "_do_", [(function(each){return smalltalk.send(stream, "_nextPut_", [smalltalk.send(aBlock, "_value_", [each])]);})]);
+return smalltalk.send(stream, "_contents", []);
 return self;}
 }),
 smalltalk.Collection);
@@ -1578,8 +1578,10 @@ selector: "withAll:",
 fn: function (aCollection) {
 var self=this;
 var instance=nil;
+var index=nil;
+(index=(1));
 (instance=smalltalk.send(self, "_new_", [smalltalk.send(aCollection, "_size", [])]));
-smalltalk.send(aCollection, "_withIndexDo_", [(function(each, index){return smalltalk.send(instance, "_at_put_", [index, each]);})]);
+smalltalk.send(aCollection, "_do_", [(function(each){smalltalk.send(instance, "_at_put_", [index, each]);return (index=((($receiver = index).klass === smalltalk.Number) ? $receiver +(1) : smalltalk.send($receiver, "__plus", [(1)])));})]);
 return instance;
 return self;}
 }),
@@ -2270,6 +2272,17 @@ return self;}
 }),
 smalltalk.String);
 
+smalltalk.addMethod(
+"_withIndexDo_",
+smalltalk.method({
+selector: "withIndexDo:",
+fn: function (aBlock) {
+var self=this;
+for(var i=0;i<self.length;i++){aBlock(self.charAt(i), i+1);};
+return self;}
+}),
+smalltalk.String);
+
 
 smalltalk.addMethod(
 "_cr",
@@ -2499,6 +2512,17 @@ return self;}
 }),
 smalltalk.Symbol);
 
+smalltalk.addMethod(
+"_collect_",
+smalltalk.method({
+selector: "collect:",
+fn: function (aBlock) {
+var self=this;
+return smalltalk.send(smalltalk.send(smalltalk.send(self, "_asString", []), "_collect_", [aBlock]), "_asSymbol", []);
+return self;}
+}),
+smalltalk.Symbol);
+
 smalltalk.addMethod(
 "_copyFrom_to_",
 smalltalk.method({
@@ -2521,6 +2545,28 @@ return self;}
 }),
 smalltalk.Symbol);
 
+smalltalk.addMethod(
+"_detect_",
+smalltalk.method({
+selector: "detect:",
+fn: function (aBlock) {
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_asString", []), "_detect_", [aBlock]);
+return self;}
+}),
+smalltalk.Symbol);
+
+smalltalk.addMethod(
+"_do_",
+smalltalk.method({
+selector: "do:",
+fn: function (aBlock) {
+var self=this;
+smalltalk.send(smalltalk.send(self, "_asString", []), "_do_", [aBlock]);
+return self;}
+}),
+smalltalk.Symbol);
+
 smalltalk.addMethod(
 "_isSymbol",
 smalltalk.method({
@@ -2543,6 +2589,17 @@ return self;}
 }),
 smalltalk.Symbol);
 
+smalltalk.addMethod(
+"_select_",
+smalltalk.method({
+selector: "select:",
+fn: function (aBlock) {
+var self=this;
+return smalltalk.send(smalltalk.send(smalltalk.send(self, "_asString", []), "_select_", [aBlock]), "_asSymbol", []);
+return self;}
+}),
+smalltalk.Symbol);
+
 smalltalk.addMethod(
 "_shallowCopy",
 smalltalk.method({
@@ -2565,6 +2622,17 @@ return self;}
 }),
 smalltalk.Symbol);
 
+smalltalk.addMethod(
+"_withIndexDo_",
+smalltalk.method({
+selector: "withIndexDo:",
+fn: function (aBlock) {
+var self=this;
+smalltalk.send(smalltalk.send(self, "_asString", []), "_withIndexDo_", [aBlock]);
+return self;}
+}),
+smalltalk.Symbol);
+
 
 smalltalk.addMethod(
 "_basicNew",

+ 107 - 9
js/Kernel-Collections.js

@@ -237,14 +237,14 @@ selector: "collect:",
 category: 'enumerating',
 fn: function (aBlock) {
 var self=this;
-var newCollection=nil;
-(newCollection=smalltalk.send(smalltalk.send(self, "_class", []), "_new", []));
-smalltalk.send(self, "_do_", [(function(each){return smalltalk.send(newCollection, "_add_", [smalltalk.send(aBlock, "_value_", [each])]);})]);
-return newCollection;
+var stream=nil;
+(stream=smalltalk.send(smalltalk.send(smalltalk.send(self, "_class", []), "_new", []), "_writeStream", []));
+smalltalk.send(self, "_do_", [(function(each){return smalltalk.send(stream, "_nextPut_", [smalltalk.send(aBlock, "_value_", [each])]);})]);
+return smalltalk.send(stream, "_contents", []);
 return self;},
 args: ["aBlock"],
-source: "collect: aBlock\x0a\x09| newCollection |\x0a\x09newCollection := self class new.\x0a\x09self do: [:each |\x0a\x09    newCollection add: (aBlock value: each)].\x0a\x09^newCollection",
-messageSends: ["new", "class", "do:", "add:", "value:"],
+source: "collect: aBlock\x0a\x09| stream |\x0a\x09stream := self class new writeStream.\x0a\x09self do: [ :each |\x0a\x09\x09stream nextPut: (aBlock value: each) ].\x0a\x09^stream contents",
+messageSends: ["writeStream", "new", "class", "do:", "nextPut:", "value:", "contents"],
 referencedClasses: []
 }),
 smalltalk.Collection);
@@ -2225,13 +2225,15 @@ category: 'instance creation',
 fn: function (aCollection) {
 var self=this;
 var instance=nil;
+var index=nil;
+(index=(1));
 (instance=smalltalk.send(self, "_new_", [smalltalk.send(aCollection, "_size", [])]));
-smalltalk.send(aCollection, "_withIndexDo_", [(function(each, index){return smalltalk.send(instance, "_at_put_", [index, each]);})]);
+smalltalk.send(aCollection, "_do_", [(function(each){smalltalk.send(instance, "_at_put_", [index, each]);return (index=((($receiver = index).klass === smalltalk.Number) ? $receiver +(1) : smalltalk.send($receiver, "__plus", [(1)])));})]);
 return instance;
 return self;},
 args: ["aCollection"],
-source: "withAll: aCollection\x0a\x09| instance |\x0a\x09instance := self new: aCollection size.\x0a\x09aCollection withIndexDo: [:each :index  |\x0a\x09\x09instance at: index put: each].\x0a\x09^instance",
-messageSends: ["new:", "size", "withIndexDo:", "at:put:"],
+source: "withAll: aCollection\x0a\x09| instance index |\x0a\x09index := 1.\x0a\x09instance := self new: aCollection size.\x0a\x09aCollection do: [:each  |\x0a\x09\x09instance at: index put: each.\x0a\x09\x09index := index + 1].\x0a\x09^instance",
+messageSends: ["new:", "size", "do:", "at:put:", "+"],
 referencedClasses: []
 }),
 smalltalk.Array.klass);
@@ -3211,6 +3213,22 @@ referencedClasses: []
 }),
 smalltalk.String);
 
+smalltalk.addMethod(
+"_withIndexDo_",
+smalltalk.method({
+selector: "withIndexDo:",
+category: 'enumerating',
+fn: function (aBlock) {
+var self=this;
+for(var i=0;i<self.length;i++){aBlock(self.charAt(i), i+1);};
+return self;},
+args: ["aBlock"],
+source: "withIndexDo: aBlock\x0a\x09<for(var i=0;i<self.length;i++){aBlock(self.charAt(i), i+1);}>",
+messageSends: [],
+referencedClasses: []
+}),
+smalltalk.String);
+
 
 smalltalk.addMethod(
 "_cr",
@@ -3540,6 +3558,22 @@ referencedClasses: []
 }),
 smalltalk.Symbol);
 
+smalltalk.addMethod(
+"_collect_",
+smalltalk.method({
+selector: "collect:",
+category: 'enumerating',
+fn: function (aBlock) {
+var self=this;
+return smalltalk.send(smalltalk.send(smalltalk.send(self, "_asString", []), "_collect_", [aBlock]), "_asSymbol", []);
+return self;},
+args: ["aBlock"],
+source: "collect: aBlock\x0a\x09^ (self asString collect: aBlock) asSymbol",
+messageSends: ["asSymbol", "collect:", "asString"],
+referencedClasses: []
+}),
+smalltalk.Symbol);
+
 smalltalk.addMethod(
 "_copyFrom_to_",
 smalltalk.method({
@@ -3572,6 +3606,38 @@ referencedClasses: []
 }),
 smalltalk.Symbol);
 
+smalltalk.addMethod(
+"_detect_",
+smalltalk.method({
+selector: "detect:",
+category: 'enumerating',
+fn: function (aBlock) {
+var self=this;
+return smalltalk.send(smalltalk.send(self, "_asString", []), "_detect_", [aBlock]);
+return self;},
+args: ["aBlock"],
+source: "detect: aBlock\x0a\x09^ self asString detect: aBlock",
+messageSends: ["detect:", "asString"],
+referencedClasses: []
+}),
+smalltalk.Symbol);
+
+smalltalk.addMethod(
+"_do_",
+smalltalk.method({
+selector: "do:",
+category: 'enumerating',
+fn: function (aBlock) {
+var self=this;
+smalltalk.send(smalltalk.send(self, "_asString", []), "_do_", [aBlock]);
+return self;},
+args: ["aBlock"],
+source: "do: aBlock\x0a\x09self asString do: aBlock",
+messageSends: ["do:", "asString"],
+referencedClasses: []
+}),
+smalltalk.Symbol);
+
 smalltalk.addMethod(
 "_isSymbol",
 smalltalk.method({
@@ -3604,6 +3670,22 @@ referencedClasses: []
 }),
 smalltalk.Symbol);
 
+smalltalk.addMethod(
+"_select_",
+smalltalk.method({
+selector: "select:",
+category: 'enumerating',
+fn: function (aBlock) {
+var self=this;
+return smalltalk.send(smalltalk.send(smalltalk.send(self, "_asString", []), "_select_", [aBlock]), "_asSymbol", []);
+return self;},
+args: ["aBlock"],
+source: "select: aBlock\x0a\x09^ (self asString select: aBlock) asSymbol",
+messageSends: ["asSymbol", "select:", "asString"],
+referencedClasses: []
+}),
+smalltalk.Symbol);
+
 smalltalk.addMethod(
 "_shallowCopy",
 smalltalk.method({
@@ -3636,6 +3718,22 @@ referencedClasses: []
 }),
 smalltalk.Symbol);
 
+smalltalk.addMethod(
+"_withIndexDo_",
+smalltalk.method({
+selector: "withIndexDo:",
+category: 'enumerating',
+fn: function (aBlock) {
+var self=this;
+smalltalk.send(smalltalk.send(self, "_asString", []), "_withIndexDo_", [aBlock]);
+return self;},
+args: ["aBlock"],
+source: "withIndexDo: aBlock\x0a\x09self asString withIndexDo: aBlock",
+messageSends: ["withIndexDo:", "asString"],
+referencedClasses: []
+}),
+smalltalk.Symbol);
+
 
 smalltalk.addMethod(
 "_basicNew",

+ 11 - 0
js/Kernel-Objects.deploy.js

@@ -1534,6 +1534,17 @@ return self;}
 }),
 smalltalk.Number);
 
+smalltalk.addMethod(
+"_abs",
+smalltalk.method({
+selector: "abs",
+fn: function () {
+var self=this;
+return Math.abs(self);;
+return self;}
+}),
+smalltalk.Number);
+
 smalltalk.addMethod(
 "_asJSON",
 smalltalk.method({

+ 16 - 0
js/Kernel-Objects.js

@@ -2194,6 +2194,22 @@ referencedClasses: []
 }),
 smalltalk.Number);
 
+smalltalk.addMethod(
+"_abs",
+smalltalk.method({
+selector: "abs",
+category: 'arithmetic',
+fn: function () {
+var self=this;
+return Math.abs(self);;
+return self;},
+args: [],
+source: "abs\x0a\x09^ <Math.abs(self);>",
+messageSends: [],
+referencedClasses: []
+}),
+smalltalk.Number);
+
 smalltalk.addMethod(
 "_asJSON",
 smalltalk.method({

File diff suppressed because it is too large
+ 857 - 542
js/Kernel-Tests.deploy.js


File diff suppressed because it is too large
+ 1234 - 779
js/Kernel-Tests.js


+ 36 - 8
st/Kernel-Collections.st

@@ -147,11 +147,11 @@ copyWithoutAll: aCollection
 !Collection methodsFor: 'enumerating'!
 
 collect: aBlock
-	| newCollection |
-	newCollection := self class new.
-	self do: [:each |
-	    newCollection add: (aBlock value: each)].
-	^newCollection
+	| stream |
+	stream := self class new writeStream.
+	self do: [ :each |
+		stream nextPut: (aBlock value: each) ].
+	^stream contents
 !
 
 detect: aBlock
@@ -854,10 +854,12 @@ with: anObject with: anObject2 with: anObject3
 !
 
 withAll: aCollection
-	| instance |
+	| instance index |
+	index := 1.
 	instance := self new: aCollection size.
-	aCollection withIndexDo: [:each :index  |
-		instance at: index put: each].
+	aCollection do: [:each  |
+		instance at: index put: each.
+		index := index + 1].
 	^instance
 ! !
 
@@ -1067,6 +1069,10 @@ shallowCopy
 
 do: aBlock
 	<for(var i=0;i<self.length;i++){aBlock(self.charAt(i));}>
+!
+
+withIndexDo: aBlock
+	<for(var i=0;i<self.length;i++){aBlock(self.charAt(i), i+1);}>
 ! !
 
 !String methodsFor: 'printing'!
@@ -1322,6 +1328,28 @@ shallowCopy
 	^self
 ! !
 
+!Symbol methodsFor: 'enumerating'!
+
+collect: aBlock
+	^ (self asString collect: aBlock) asSymbol
+!
+
+detect: aBlock
+	^ self asString detect: aBlock
+!
+
+do: aBlock
+	self asString do: aBlock
+!
+
+select: aBlock
+	^ (self asString select: aBlock) asSymbol
+!
+
+withIndexDo: aBlock
+	self asString withIndexDo: aBlock
+! !
+
 !Symbol methodsFor: 'printing'!
 
 isSymbol

+ 4 - 0
st/Kernel-Objects.st

@@ -756,6 +756,10 @@ identityHash
 	<return self % aNumber>
 !
 
+abs
+	^ <Math.abs(self);>
+!
+
 max: aNumber
 	<return Math.max(self, aNumber);>
 !

+ 405 - 197
st/Kernel-Tests.st

@@ -1,45 +1,4 @@
 Smalltalk current createPackage: 'Kernel-Tests' properties: #{}!
-TestCase subclass: #ArrayTest
-	instanceVariableNames: ''
-	package: 'Kernel-Tests'!
-
-!ArrayTest methodsFor: 'testing'!
-
-testAtIfAbsent
-	| array |
-	array := #('hello' 'world').
-	self assert: (array at: 1) equals: 'hello'.
-	self assert: (array at: 2) equals: 'world'.
-	self assert: (array at: 2 ifAbsent: ['not found']) equals: 'world'.
-	self assert: (array at: 0 ifAbsent: ['not found']) equals: 'not found'.
-	self assert: (array at: -10 ifAbsent: ['not found']) equals: 'not found'.
-	self assert: (array at: 3 ifAbsent: ['not found']) equals: 'not found'.
-!
-
-testFirstN
-	self assert: {1. 2. 3} equals: ({1. 2. 3. 4. 5} first: 3).
-!
-
-testIfEmpty
-	self assert: 'zork' equals: ( '' ifEmpty: ['zork'] )
-!
-
-testPrintString
-	| array |
-	array := Array new.
-	self assert: 'a Array ()' equals: ( array printString ).
-	array add: 1; add: 3.
-	self assert: 'a Array (1 3)' equals: ( array printString ).
-	array add: 'foo'.
-	self assert: 'a Array (1 3 ''foo'')' equals: ( array printString ).
-	array remove: 1; remove: 3.
-	self assert: 'a Array (''foo'')' equals: ( array printString ).
-	array addLast: 3.
-	self assert: 'a Array (''foo'' 3)' equals: ( array printString ).
-	array addLast: 3.
-	self assert: 'a Array (''foo'' 3 3)' equals: ( array printString ).
-! !
-
 TestCase subclass: #BlockClosureTest
 	instanceVariableNames: ''
 	package: 'Kernel-Tests'!
@@ -234,8 +193,12 @@ collectionClass
 	^ self class collectionClass
 !
 
+collectionWithDuplicates
+	^ self collectionClass withAll: #('a' 'b' 'c' 1 2 1 'a')
+!
+
 defaultValues
-	^ #('a' 1 2 #e)
+	^ #(1 2 3 -4)
 ! !
 
 !CollectionTest methodsFor: 'convenience'!
@@ -243,11 +206,17 @@ defaultValues
 assertSameContents: aCollection 	as: anotherCollection
 	self assert: aCollection size = anotherCollection size.
 	aCollection do: [ :each |
-		self assert: (aCollection at: each) = (anotherCollection at: each) ]
+		self assert: (aCollection occurrencesOf: each) = (anotherCollection occurrencesOf: each) ]
 ! !
 
 !CollectionTest methodsFor: 'testing'!
 
+isCollectionReadOnly
+	^ false
+! !
+
+!CollectionTest methodsFor: 'tests'!
+
 testAsArray
 	self 
 		assertSameContents: self collection 
@@ -262,18 +231,53 @@ testAsOrderedCollection
 
 testAsSet
 	| c set |
-	c := self collectionClass withAll: #('a' 'b' 'c' 1 2 1 'a').
+	c := self collectionWithDuplicates.
 	set := c asSet.
 	self assert: set size = 5.
 	c do: [ :each |
 		self assert: (set includes: each) ]
 !
 
+testCollect
+	| newCollection |
+	newCollection :=  #(1 2 3 4).
+	self 
+		assertSameContents: (self collection collect: [ :each |
+			each abs ])
+		as: newCollection
+!
+
+testDetect
+	self assert: (self collection detect: [ :each | each < 0 ]) = -4.
+	self 
+		should: [ self collection detect: [ :each | each = 6 ] ]
+		raise: Error
+!
+
+testDo
+	| newCollection |
+	newCollection := OrderedCollection new.
+	self collection do: [ :each |
+		newCollection add: each ].
+	self 
+		assertSameContents: self collection 
+		as: newCollection
+!
+
 testIsEmpty
 	self assert: self collectionClass new isEmpty.
 	self deny: self collection isEmpty
 !
 
+testSelect
+	| newCollection |
+	newCollection := #(2 -4).
+	self 
+		assertSameContents: (self collection select: [ :each |
+			each even ])
+		as: newCollection
+!
+
 testSize
 	self assert: self collectionClass new size = 0.
 	self assert: self collection size = 4
@@ -288,13 +292,56 @@ collectionClass
 !CollectionTest class methodsFor: 'testing'!
 
 isAbstract
-	^ self collectionClass notNil
+	^ self collectionClass isNil
 ! !
 
-TestCase subclass: #DictionaryTest
+CollectionTest subclass: #HashedCollectionTest
 	instanceVariableNames: ''
 	package: 'Kernel-Tests'!
 
+!HashedCollectionTest methodsFor: 'accessing'!
+
+collection
+	^ #{ 'a' -> 1. 'b' -> 2. 'c' -> 3. 'd' -> -4 }
+!
+
+collectionWithDuplicates
+	^ #{ 'a' -> 1. 'b' -> 2. 'c' -> 3. 'd' -> -4. 'e' -> 1. 'f' -> 2. 'g' -> 10 }
+! !
+
+!HashedCollectionTest class methodsFor: 'accessing'!
+
+collectionClass
+	^ HashedCollection
+! !
+
+HashedCollectionTest subclass: #DictionaryTest
+	instanceVariableNames: ''
+	package: 'Kernel-Tests'!
+
+!DictionaryTest methodsFor: 'accessing'!
+
+collection
+	^ Dictionary new
+		at: 1 put: 1;
+		at: 'a' put: 2;
+		at: true put: 3;
+		at: 4 put: -4;
+		yourself
+!
+
+collectionWithDuplicates
+	^ Dictionary new
+		at: 1 put: 1;
+		at: 'a' put: 2;
+		at: true put: 3;
+		at: 4 put: -4;
+		at: 'b' put: 1;
+		at: 3 put: 3;
+		at: false put: 12;
+		yourself
+! !
+
 !DictionaryTest methodsFor: 'tests'!
 
 testAccessing
@@ -455,6 +502,313 @@ testValues
 	self assert: d values = #(2 3 4)
 ! !
 
+!DictionaryTest class methodsFor: 'accessing'!
+
+collectionClass
+	^ Dictionary
+! !
+
+CollectionTest subclass: #SequenceableCollectionTest
+	instanceVariableNames: ''
+	package: 'Kernel-Tests'!
+
+!SequenceableCollectionTest methodsFor: 'tests'!
+
+testAt
+	self assert: (self collection at: 4) = -4.
+	self should: [ self collection at: 5 ] raise: Error
+!
+
+testAtIfAbsent
+	self assert: (self collection at: (self collection size + 1) ifAbsent: [ 'none' ]) = 'none'
+! !
+
+SequenceableCollectionTest subclass: #ArrayTest
+	instanceVariableNames: ''
+	package: 'Kernel-Tests'!
+
+!ArrayTest methodsFor: 'testing'!
+
+testAtIfAbsent
+	| array |
+	array := #('hello' 'world').
+	self assert: (array at: 1) equals: 'hello'.
+	self assert: (array at: 2) equals: 'world'.
+	self assert: (array at: 2 ifAbsent: ['not found']) equals: 'world'.
+	self assert: (array at: 0 ifAbsent: ['not found']) equals: 'not found'.
+	self assert: (array at: -10 ifAbsent: ['not found']) equals: 'not found'.
+	self assert: (array at: 3 ifAbsent: ['not found']) equals: 'not found'.
+!
+
+testFirstN
+	self assert: {1. 2. 3} equals: ({1. 2. 3. 4. 5} first: 3).
+!
+
+testIfEmpty
+	self assert: 'zork' equals: ( '' ifEmpty: ['zork'] )
+!
+
+testPrintString
+	| array |
+	array := Array new.
+	self assert: 'a Array ()' equals: ( array printString ).
+	array add: 1; add: 3.
+	self assert: 'a Array (1 3)' equals: ( array printString ).
+	array add: 'foo'.
+	self assert: 'a Array (1 3 ''foo'')' equals: ( array printString ).
+	array remove: 1; remove: 3.
+	self assert: 'a Array (''foo'')' equals: ( array printString ).
+	array addLast: 3.
+	self assert: 'a Array (''foo'' 3)' equals: ( array printString ).
+	array addLast: 3.
+	self assert: 'a Array (''foo'' 3 3)' equals: ( array printString ).
+! !
+
+!ArrayTest class methodsFor: 'accessing'!
+
+collectionClass
+	^ Array
+! !
+
+SequenceableCollectionTest subclass: #StringTest
+	instanceVariableNames: ''
+	package: 'Kernel-Tests'!
+
+!StringTest methodsFor: 'accessing'!
+
+collection
+	^'hello'
+!
+
+collectionWithDuplicates
+	^ 'abbaerte'
+! !
+
+!StringTest methodsFor: 'tests'!
+
+testAddRemove
+	self should: ['hello' add: 'a'] raise: Error.
+	self should: ['hello' remove: 'h'] raise: Error
+!
+
+testAsArray
+	self assert: 'hello' asArray = #('h' 'e' 'l' 'l' 'o').
+!
+
+testAt
+	self assert: ('hello' at: 1) = 'h'.
+	self assert: ('hello' at: 5) = 'o'.
+	self assert: ('hello' at: 6 ifAbsent: [nil]) = nil
+!
+
+testAtPut
+	"String instances are read-only"
+	self should: ['hello' at: 1 put: 'a'] raise: Error
+!
+
+testCollect
+	| newCollection |
+	newCollection := 'hheelllloo'.
+	self 
+		assertSameContents: (self collection collect: [ :each |
+			each, each ])
+		as: newCollection
+!
+
+testCopyWithoutAll
+	self 
+		assert: 'hello world' 
+		equals: ('*hello* *world*' copyWithoutAll: '*')
+!
+
+testDetect
+	self assert: (self collection detect: [ :each | each = 'h' ]) = 'h'.
+	self 
+		should: [ self collection detect: [ :each | each = 6 ] ]
+		raise: Error
+!
+
+testEquality
+	self assert: 'hello' = 'hello'.
+	self deny: 'hello' = 'world'.
+
+	self assert: 'hello'  = 'hello' yourself.
+	self assert: 'hello' yourself = 'hello'.
+
+	"test JS falsy value"
+	self deny: '' = 0
+!
+
+testIdentity
+	self assert: 'hello' == 'hello'.
+	self deny: 'hello' == 'world'.
+
+	self assert: 'hello' == 'hello' yourself.
+	self assert: 'hello' yourself == 'hello'.
+
+	"test JS falsy value"
+	self deny: '' == 0
+!
+
+testIncludesSubString
+	self assert: ('amber' includesSubString: 'ber').
+	self deny: ('amber' includesSubString: 'zork').
+!
+
+testJoin
+	self assert: 'hello,world' equals: (',' join: #('hello' 'world'))
+!
+
+testSelect
+	| newCollection |
+	newCollection := 'o'.
+	self 
+		assertSameContents: (self collection select: [ :each |
+			each = 'o' ])
+		as: newCollection
+!
+
+testSize
+	self assert: 'smalltalk' size equals: 9.
+	self assert: '' size equals: 0
+!
+
+testStreamContents
+	self 
+		assert: 'hello world' 
+		equals: (String streamContents: [ :aStream | 
+			aStream 
+				nextPutAll: 'hello'; space; 
+				nextPutAll: 'world' ])
+! !
+
+!StringTest class methodsFor: 'accessing'!
+
+collectionClass
+	^ String
+! !
+
+SequenceableCollectionTest subclass: #SymbolTest
+	instanceVariableNames: ''
+	package: 'Kernel-Tests'!
+
+!SymbolTest methodsFor: 'accessing'!
+
+collection
+	^ #hello
+!
+
+collectionWithDuplicates
+	^ #phhaaarorra
+! !
+
+!SymbolTest methodsFor: 'tests'!
+
+testAsString
+	self assert: #hello asString equals: 'hello'
+!
+
+testAsSymbol
+	self assert: #hello == #hello asSymbol
+!
+
+testAt
+	self assert: (#hello at: 1) = 'h'.
+	self assert: (#hello at: 5) = 'o'.
+	self assert: (#hello at: 6 ifAbsent: [nil]) = nil
+!
+
+testAtPut
+	"Symbol instances are read-only"
+	self should: ['hello' at: 1 put: 'a'] raise: Error
+!
+
+testCollect
+	| newCollection |
+	newCollection := #hheelllloo.
+	self 
+		assertSameContents: (self collection collect: [ :each |
+			each, each ])
+		as: newCollection
+!
+
+testComparing
+	self assert: #ab > #aa.
+	self deny: #ab > #ba.
+
+	self assert: #ab < #ba.
+	self deny: #bb < #ba.
+
+	self assert: #ab >= #aa.
+	self deny: #ab >= #ba.
+
+	self assert: #ab <= #ba.
+	self deny: #bb <= #ba
+!
+
+testCopying
+	self assert: #hello copy == #hello.
+	self assert: #hello deepCopy == #hello
+!
+
+testDetect
+	self assert: (self collection detect: [ :each | each = 'h' ]) = 'h'.
+	self 
+		should: [ self collection detect: [ :each | each = 'z' ] ]
+		raise: Error
+!
+
+testEquality
+	self assert: #hello = #hello.
+	self deny: #hello = #world.
+
+	self assert: #hello  = #hello yourself.
+	self assert: #hello yourself = #hello.
+
+	self deny: #hello  = 'hello'.
+	self deny: 'hello' = #hello.
+!
+
+testIdentity
+	self assert: #hello == #hello.
+	self deny: #hello == #world.
+
+	self assert: #hello  = #hello yourself.
+	self assert: #hello yourself = #hello asString asSymbol
+!
+
+testIsEmpty
+	self deny: self collection isEmpty.
+	self assert: '' asSymbol isEmpty
+!
+
+testIsSymbolIsString
+	self assert: #hello isSymbol.
+	self deny: 'hello' isSymbol.
+	self deny: #hello isString.
+	self assert: 'hello' isString
+!
+
+testSelect
+	| newCollection |
+	newCollection := 'o'.
+	self 
+		assertSameContents: (self collection select: [ :each |
+			each = 'o' ])
+		as: newCollection
+!
+
+testSize
+	self assert: #a size equals: 1.
+	self assert: #aaaaa size equals: 5
+! !
+
+!SymbolTest class methodsFor: 'accessing'!
+
+collectionClass
+	^ Symbol
+! !
+
 TestCase subclass: #JSObjectProxyTest
 	instanceVariableNames: ''
 	package: 'Kernel-Tests'!
@@ -518,6 +872,11 @@ TestCase subclass: #NumberTest
 
 !NumberTest methodsFor: 'tests'!
 
+testAbs
+	self assert: 4 abs = 4.
+	self assert: -4 abs = 4
+!
+
 testArithmetic
 	
 	"We rely on JS here, so we won't test complex behavior, just check if 
@@ -957,157 +1316,6 @@ testUnicity
 	self assert: set asArray equals: #(21 'hello')
 ! !
 
-TestCase subclass: #StringTest
-	instanceVariableNames: ''
-	package: 'Kernel-Tests'!
-
-!StringTest methodsFor: 'tests'!
-
-testAddRemove
-	self should: ['hello' add: 'a'] raise: Error.
-	self should: ['hello' remove: 'h'] raise: Error
-!
-
-testAsArray
-	self assert: 'hello' asArray = #('h' 'e' 'l' 'l' 'o').
-!
-
-testAt
-	self assert: ('hello' at: 1) = 'h'.
-	self assert: ('hello' at: 5) = 'o'.
-	self assert: ('hello' at: 6 ifAbsent: [nil]) = nil
-!
-
-testAtPut
-	"String instances are read-only"
-	self should: ['hello' at: 1 put: 'a'] raise: Error
-!
-
-testCopyWithoutAll
-	self 
-		assert: 'hello world' 
-		equals: ('*hello* *world*' copyWithoutAll: '*')
-!
-
-testEquality
-	self assert: 'hello' = 'hello'.
-	self deny: 'hello' = 'world'.
-
-	self assert: 'hello'  = 'hello' yourself.
-	self assert: 'hello' yourself = 'hello'.
-
-	"test JS falsy value"
-	self deny: '' = 0
-!
-
-testIdentity
-	self assert: 'hello' == 'hello'.
-	self deny: 'hello' == 'world'.
-
-	self assert: 'hello' == 'hello' yourself.
-	self assert: 'hello' yourself == 'hello'.
-
-	"test JS falsy value"
-	self deny: '' == 0
-!
-
-testIncludesSubString
-	self assert: ('amber' includesSubString: 'ber').
-	self deny: ('amber' includesSubString: 'zork').
-!
-
-testJoin
-	self assert: 'hello,world' equals: (',' join: #('hello' 'world'))
-!
-
-testSize
-	self assert: 'smalltalk' size equals: 9.
-	self assert: '' size equals: 0
-!
-
-testStreamContents
-	self 
-		assert: 'hello world' 
-		equals: (String streamContents: [:aStream| aStream 
-                                                 					nextPutAll: 'hello'; space; 
-                                                 					nextPutAll: 'world'])
-! !
-
-TestCase subclass: #SymbolTest
-	instanceVariableNames: ''
-	package: 'Kernel-Tests'!
-
-!SymbolTest methodsFor: 'tests'!
-
-testAsString
-	self assert: #hello asString equals: 'hello'
-!
-
-testAsSymbol
-	self assert: #hello == #hello asSymbol
-!
-
-testAt
-	self assert: (#hello at: 1) = 'h'.
-	self assert: (#hello at: 5) = 'o'.
-	self assert: (#hello at: 6 ifAbsent: [nil]) = nil
-!
-
-testAtPut
-	"Symbol instances are read-only"
-	self should: ['hello' at: 1 put: 'a'] raise: Error
-!
-
-testComparing
-	self assert: #ab > #aa.
-	self deny: #ab > #ba.
-
-	self assert: #ab < #ba.
-	self deny: #bb < #ba.
-
-	self assert: #ab >= #aa.
-	self deny: #ab >= #ba.
-
-	self assert: #ab <= #ba.
-	self deny: #bb <= #ba
-!
-
-testCopying
-	self assert: #hello copy == #hello.
-	self assert: #hello deepCopy == #hello
-!
-
-testEquality
-	self assert: #hello = #hello.
-	self deny: #hello = #world.
-
-	self assert: #hello  = #hello yourself.
-	self assert: #hello yourself = #hello.
-
-	self deny: #hello  = 'hello'.
-	self deny: 'hello' = #hello.
-!
-
-testIdentity
-	self assert: #hello == #hello.
-	self deny: #hello == #world.
-
-	self assert: #hello  = #hello yourself.
-	self assert: #hello yourself = #hello asString asSymbol
-!
-
-testIsSymbolIsString
-	self assert: #hello isSymbol.
-	self deny: 'hello' isSymbol.
-	self deny: #hello isString.
-	self assert: 'hello' isString
-!
-
-testSize
-	self assert: #a size equals: 1.
-	self assert: #aaaaa size equals: 5
-! !
-
 TestCase subclass: #UndefinedTest
 	instanceVariableNames: ''
 	package: 'Kernel-Tests'!

Some files were not shown because too many files changed in this diff