RegressionTests__CollectionTests.st
changeset 1447 2351db93aa5b
parent 1424 56c64e1f572e
child 1500 d406a10b2965
child 1651 8d2368bccccb
--- a/RegressionTests__CollectionTests.st	Wed Jun 29 13:00:17 2016 +0000
+++ b/RegressionTests__CollectionTests.st	Wed Jun 29 15:55:29 2016 +0200
@@ -1,4 +1,4 @@
-"{ Package: 'exept:regression' }"
+"{ Package: 'stx:goodies/regression' }"
 
 "{ NameSpace: RegressionTests }"
 
@@ -27,7 +27,7 @@
     documentation to be added.
 
     [author:]
-        Claus Gittinger (cg@alan)
+	Claus Gittinger (cg@alan)
 
     [see also:]
 
@@ -51,8 +51,8 @@
     "is it sorted?"
     first := true.
     aSortedCollection inject:nil into:[:last :each|
-            first ifTrue:[first := false] 
-                  ifFalse:[self assert:(sortBlock value:last value:each)]. each].
+	    first ifTrue:[first := false]
+		  ifFalse:[self assert:(sortBlock value:last value:each)]. each].
 
     "same elements as in original?"
     self assert:(aSortedCollection asBag = anOriginalCollection asBag).
@@ -69,35 +69,35 @@
 !CollectionTests methodsFor:'initialize-release'!
 
 setUp
-        empty := Set new.
-        nonEmpty := OrderedCollection with: #x.
+	empty := Set new.
+	nonEmpty := OrderedCollection with: #x.
 ! !
 
 !CollectionTests methodsFor:'tests-byteArray'!
 
 testByteArrayReverse
      1 to:1024 do:[:i|
-        |bytes test rBytes|
+	|bytes test rBytes|
 
-        bytes := ((1 to:i) asArray collect:[:i | i bitAnd:255]) asByteArray.
-        test := ((i to:1 by:-1) asArray collect:[:i | i bitAnd:255]) asByteArray.
-        rBytes := bytes copy.
-        self assert:(rBytes reverse = test).
+	bytes := ((1 to:i) asArray collect:[:i | i bitAnd:255]) asByteArray.
+	test := ((i to:1 by:-1) asArray collect:[:i | i bitAnd:255]) asByteArray.
+	rBytes := bytes copy.
+	self assert:(rBytes reverse = test).
 
-        rBytes := bytes copy.
-        self assert:(rBytes reverse reverse = bytes).
+	rBytes := bytes copy.
+	self assert:(rBytes reverse reverse = bytes).
      ].
 !
 
 testByteArrayReversed
      1 to:1024 do:[:i|
-        |bytes test rBytes|
+	|bytes test rBytes|
 
-        bytes := ((1 to:i) asArray collect:[:i | i bitAnd:255]) asByteArray.
-        test := ((i to:1 by:-1) asArray collect:[:i | i bitAnd:255]) asByteArray.
-        self assert:(bytes reversed = test).
+	bytes := ((1 to:i) asArray collect:[:i | i bitAnd:255]) asByteArray.
+	test := ((i to:1 by:-1) asArray collect:[:i | i bitAnd:255]) asByteArray.
+	self assert:(bytes reversed = test).
 
-        self assert:(bytes reversed reversed = bytes).
+	self assert:(bytes reversed reversed = bytes).
      ].
 ! !
 
@@ -277,9 +277,9 @@
     coll2 := coll1 copy.
     self assert: (coll1 size == coll2 size).
     1 to:coll1 size do:[:i |
-        "/ coll1 at:10
-        "/ coll2 at:10
-        self assert:(coll1 at:i) = (coll2 at:i).
+	"/ coll1 at:10
+	"/ coll2 at:10
+	self assert:(coll1 at:i) = (coll2 at:i).
     ].
     self assert: ( coll2 = coll1 ).
 
@@ -301,27 +301,27 @@
 
 protoCollectionFor: aClass
     aClass == BooleanArray ifTrue: [
-        ^ BooleanArray withAll:#(true false true true false false true false false true)
+	^ BooleanArray withAll:#(true false true true false false true false false true)
     ].
     aClass == BitArray ifTrue: [
-        ^ BitArray withAll:#(1 0 1 1 0 0 1 0 0 1)
+	^ BitArray withAll:#(1 0 1 1 0 0 1 0 0 1)
     ].
     aClass == ByteArray ifTrue: [
-        ^ ByteArray withAll:#(1 2 3 4 16rFC 16rFD 16rFE 16rFF)
+	^ ByteArray withAll:#(1 2 3 4 16rFC 16rFD 16rFE 16rFF)
     ].
     aClass == String ifTrue: [
-        ^ 'abcdefghijklmnopqrstuvwxyz'
+	^ 'abcdefghijklmnopqrstuvwxyz'
     ].
     (aClass includesBehavior:CharacterArray) ifTrue:[
-        ^ 'abcdefghijklmnopqrstuvwxyz' as: aClass         
+	^ 'abcdefghijklmnopqrstuvwxyz' as: aClass
     ].
-    (aClass includesBehavior:AbstractNumberVector) ifTrue:[   
-        (aClass includesBehavior:UnboxedIntegerArray) ifTrue:[   
-            ^ #(1 2 3 4 5 6 7 8 9 10) as: aClass         
-        ].
-        ^ #(1.0 2 3.0 4 5.0 6 7.0 8 9.0 10) as: aClass         
+    (aClass includesBehavior:AbstractNumberVector) ifTrue:[
+	(aClass includesBehavior:UnboxedIntegerArray) ifTrue:[
+	    ^ #(1 2 3 4 5 6 7 8 9 10) as: aClass
+	].
+	^ #(1.0 2 3.0 4 5.0 6 7.0 8 9.0 10) as: aClass
     ].
-    ^ #(1 true 2.0 false 3 nil 4.0 5 6.0 7 8.0 9 10.0) as: aClass         
+    ^ #(1 true 2.0 false 3 nil 4.0 5 6.0 7 8.0 9 10.0) as: aClass
 
     "
      self basicNew testSequentialCollectionOperations
@@ -334,14 +334,14 @@
     |classes|
 
     classes := OrderedCollection new.
-    classes 
-        add:Dictionary;
-        add:IdentityDictionary;
-        add:OrderedDictionary;
-        add:BTree.
+    classes
+	add:Dictionary;
+	add:IdentityDictionary;
+	add:OrderedDictionary;
+	add:BTree.
 
     classes do:[:eachClass |
-        self doTestDictionaryLikeAddRemoveOperationsIn:eachClass
+	self doTestDictionaryLikeAddRemoveOperationsIn:eachClass
     ].
 
     "
@@ -355,24 +355,24 @@
     |classes|
 
     classes := OrderedCollection new.
-    classes 
-        "/ add:RunArray;
-        add:Bag;
-        add:Set;
-        add:IdentitySet;
-        "/add:Dictionary;
-        "/add:IdentityDictionary;
-        add:OrderedCollection;
-        add:SortedCollection;
-        "/add:Queue;
-        "/add:Stack;
-        add:SortedCollection;
-        "/add:OrderedDictionary;
-        add:OrderedSet.
-        "/add:BTree.
+    classes
+	"/ add:RunArray;
+	add:Bag;
+	add:Set;
+	add:IdentitySet;
+	"/add:Dictionary;
+	"/add:IdentityDictionary;
+	add:OrderedCollection;
+	add:SortedCollection;
+	"/add:Queue;
+	"/add:Stack;
+	add:SortedCollection;
+	"/add:OrderedDictionary;
+	add:OrderedSet.
+	"/add:BTree.
 
     classes do:[:eachClass |
-        self doTestGeneralAddRemoveOperationsIn:eachClass
+	self doTestGeneralAddRemoveOperationsIn:eachClass
     ].
 
     "
@@ -386,24 +386,24 @@
     |classes|
 
     classes := OrderedCollection new.
-    classes 
-        add:RunArray;
-        add:Bag;
-        add:Set;
-        add:IdentitySet;
-        add:Dictionary;
-        add:IdentityDictionary;
-        add:OrderedCollection;
-        add:SortedCollection;
-        add:Queue;
-        add:Stack;
-        add:SortedCollection;
-        add:OrderedDictionary;
-        add:OrderedSet;
-        add:BTree.
+    classes
+	add:RunArray;
+	add:Bag;
+	add:Set;
+	add:IdentitySet;
+	add:Dictionary;
+	add:IdentityDictionary;
+	add:OrderedCollection;
+	add:SortedCollection;
+	add:Queue;
+	add:Stack;
+	add:SortedCollection;
+	add:OrderedDictionary;
+	add:OrderedSet;
+	add:BTree.
 
     classes do:[:eachClass |
-        self doTestGeneralCollectionOperationsIn:eachClass
+	self doTestGeneralCollectionOperationsIn:eachClass
     ].
 
     "
@@ -417,28 +417,28 @@
     |classes|
 
     classes := OrderedCollection new.
-    classes 
-        add:OrderedCollection;
-        add:Array;
-        add:String;
-        add:ByteArray;
-        add:WordArray;
-        add:IntegerArray;
-        add:LongIntegerArray;
-        add:SignedWordArray;
-        add:SignedIntegerArray;
-        add:SignedLongIntegerArray;
-        add:FloatArray;
-        add:DoubleArray;
-        add:HalfFloatArray;
-        add:TwoByteString;
-        add:Unicode16String;
-        add:Unicode32String;
-        add:BooleanArray;
-        add:BitArray.
+    classes
+	add:OrderedCollection;
+	add:Array;
+	add:String;
+	add:ByteArray;
+	add:WordArray;
+	add:IntegerArray;
+	add:LongIntegerArray;
+	add:SignedWordArray;
+	add:SignedIntegerArray;
+	add:SignedLongIntegerArray;
+	add:FloatArray;
+	add:DoubleArray;
+	add:HalfFloatArray;
+	add:TwoByteString;
+	add:Unicode16String;
+	add:Unicode32String;
+	add:BooleanArray;
+	add:BitArray.
 
     classes do:[:eachClass |
-        self doTestSequentialCollectionOperationsIn:eachClass
+	self doTestSequentialCollectionOperationsIn:eachClass
     ].
 
     "
@@ -581,13 +581,13 @@
     lastTestData := nil.
 
     errs := col inject: 0 into:
-            [ :totIn :aSortTestData | |totOut|
-            totOut := totIn.
-            lastTestData notNil ifTrue:
-                    [ lastTestData value = aSortTestData value ifTrue:
-                            [ lastTestData order > aSortTestData order ifTrue: [ totOut := totOut + 1 ] ] ].
-            lastTestData := aSortTestData.
-            totOut ].
+	    [ :totIn :aSortTestData | |totOut|
+	    totOut := totIn.
+	    lastTestData notNil ifTrue:
+		    [ lastTestData value = aSortTestData value ifTrue:
+			    [ lastTestData order > aSortTestData order ifTrue: [ totOut := totOut + 1 ] ] ].
+	    lastTestData := aSortTestData.
+	    totOut ].
     self should: [ errs = 0 ]
 
     "
@@ -627,7 +627,7 @@
     self assert:( col2 sameContentsAs: (1 to:10000) ).
 
     "
-     self new testOrderedCollection01_Sort1  
+     self new testOrderedCollection01_Sort1
     "
 
     "Modified: / 04-07-2011 / 19:29:54 / cg"
@@ -639,14 +639,14 @@
     size := 12500.
     col := OrderedCollection new.
     1 to:size do:[:el|
-        col add:nil.
+	col add:nil.
     ].
-    sortBlock := [:entry1 :entry2 |  
-        ((entry1 isNil) or:[entry2 isNil]) ifTrue:[
-            true
-        ] ifFalse:[
-            false
-        ]
+    sortBlock := [:entry1 :entry2 |
+	((entry1 isNil) or:[entry2 isNil]) ifTrue:[
+	    true
+	] ifFalse:[
+	    false
+	]
     ].
     self shouldnt:[col sort:sortBlock] raise:RecursionInterruptSignal.
 
@@ -661,7 +661,7 @@
     size := 12500.
     col := OrderedCollection new.
     1 to:size do:[:el|
-        col add:'abc'.
+	col add:'abc'.
     ].
     self shouldnt:[col sort] raise:RecursionInterruptSignal.
 
@@ -676,14 +676,14 @@
     size := 125.
     col := OrderedCollection new.
     1 to:size do:[:el|
-        col add:nil.
+	col add:nil.
     ].
-    sortBlock := [:entry1 :entry2 |  
-        ((entry1 isNil) or:[entry2 isNil]) ifTrue:[
-            true
-        ] ifFalse:[
-            false
-        ]
+    sortBlock := [:entry1 :entry2 |
+	((entry1 isNil) or:[entry2 isNil]) ifTrue:[
+	    true
+	] ifFalse:[
+	    false
+	]
     ].
     "/ col sort:sortBlock.
     self shouldnt:[col sort:sortBlock] raise:RecursionInterruptSignal.
@@ -695,84 +695,84 @@
 
 testOrderedCollection05_SortRandomCollection
      |data sorted rg coData checkBlock|
-    
-     checkBlock := [:a :b| a <= b].   
+
+     checkBlock := [:a :b| a <= b].
      rg := Random new.
 
      #(1 4 11 2000 20011 200000) do:[:eachSize|
-         data := Array new:eachSize.
-         1 to:data size do:[:i |
-            data at:i put:(rg nextIntegerBetween:1 and:100).
-         ].
-         sorted := data copy sort.
-         self checkSorted:sorted with:checkBlock against:data.
-         sorted := sorted sort.
-         self checkSorted:sorted with:checkBlock against:data.
-         sorted := sorted reverse sort.
-         self checkSorted:sorted with:checkBlock against:data.
+	 data := Array new:eachSize.
+	 1 to:data size do:[:i |
+	    data at:i put:(rg nextIntegerBetween:1 and:100).
+	 ].
+	 sorted := data copy sort.
+	 self checkSorted:sorted with:checkBlock against:data.
+	 sorted := sorted sort.
+	 self checkSorted:sorted with:checkBlock against:data.
+	 sorted := sorted reverse sort.
+	 self checkSorted:sorted with:checkBlock against:data.
 
-         coData := data copy.   
-         sorted := data copy sortWith:coData.
-         self checkSorted:sorted with:checkBlock against:data.
-         self checkSorted:coData with:checkBlock against:data.
+	 coData := data copy.
+	 sorted := data copy sortWith:coData.
+	 self checkSorted:sorted with:checkBlock against:data.
+	 self checkSorted:coData with:checkBlock against:data.
 
 "/ Policy is not yet supported (without libcompat)
 "/         sorted := data copy sort:[:policy :a :b| a < b].
 "/         self checkSorted:sorted with:checkBlock against:data.
 
-         sorted := data copy sort:[:a :b| a < b].
-         self checkSorted:sorted with:checkBlock against:data.
+	 sorted := data copy sort:[:a :b| a < b].
+	 self checkSorted:sorted with:checkBlock against:data.
 
-         coData := data copy.   
-         sorted := data copy sort:[:a :b| a < b] with:coData.
-         self checkSorted:sorted with:checkBlock against:data.
-         self checkSorted:coData with:checkBlock against:data.
+	 coData := data copy.
+	 sorted := data copy sort:[:a :b| a < b] with:coData.
+	 self checkSorted:sorted with:checkBlock against:data.
+	 self checkSorted:coData with:checkBlock against:data.
     ].
 !
 
 testOrderedCollection06_MergeSortRandomCollection
      |data sorted rg checkBlock|
-    
-     checkBlock := [:a :b| a <= b].   
+
+     checkBlock := [:a :b| a <= b].
      rg := Random new.
 
      #(1 4 11 2000 20011 200000) do:[:eachSize|
-         data := Array new:eachSize.
-         1 to:data size do:[:i |
-            data at:i put:(rg nextIntegerBetween:1 and:100).
-         ].
-         sorted := data copy mergeSort.
-         self checkSorted:sorted with:checkBlock against:data.
-         sorted := sorted mergeSort.
-         self checkSorted:sorted with:checkBlock against:data.
-         sorted := sorted reverse mergeSort.
-         self checkSorted:sorted with:checkBlock against:data.
+	 data := Array new:eachSize.
+	 1 to:data size do:[:i |
+	    data at:i put:(rg nextIntegerBetween:1 and:100).
+	 ].
+	 sorted := data copy mergeSort.
+	 self checkSorted:sorted with:checkBlock against:data.
+	 sorted := sorted mergeSort.
+	 self checkSorted:sorted with:checkBlock against:data.
+	 sorted := sorted reverse mergeSort.
+	 self checkSorted:sorted with:checkBlock against:data.
 
-         sorted := data copy mergeSort:[:a :b| a < b].
-         self checkSorted:sorted with:checkBlock against:data.
+	 sorted := data copy mergeSort:[:a :b| a < b].
+	 self checkSorted:sorted with:checkBlock against:data.
     ].
 !
 
 testOrderedCollection07_HeapSortRandomCollection
      |data sorted rg checkBlock|
-    
-     checkBlock := [:a :b| a <= b].   
+
+     checkBlock := [:a :b| a <= b].
      rg := Random new.
 
      #(1 4 11 2000 20011 200000) do:[:eachSize|
-         data := Array new:eachSize.
-         1 to:data size do:[:i |
-            data at:i put:(rg nextIntegerBetween:1 and:100).
-         ].
-         sorted := data copy heapSort.
-         self checkSorted:sorted with:checkBlock against:data.
-         sorted := sorted heapSort.
-         self checkSorted:sorted with:checkBlock against:data.
-         sorted := sorted reverse heapSort.
-         self checkSorted:sorted with:checkBlock against:data.
+	 data := Array new:eachSize.
+	 1 to:data size do:[:i |
+	    data at:i put:(rg nextIntegerBetween:1 and:100).
+	 ].
+	 sorted := data copy heapSort.
+	 self checkSorted:sorted with:checkBlock against:data.
+	 sorted := sorted heapSort.
+	 self checkSorted:sorted with:checkBlock against:data.
+	 sorted := sorted reverse heapSort.
+	 self checkSorted:sorted with:checkBlock against:data.
 
-         sorted := data copy heapSort:[:a :b| a < b].
-         self checkSorted:sorted with:checkBlock against:data.
+	 sorted := data copy heapSort:[:a :b| a < b].
+	 self checkSorted:sorted with:checkBlock against:data.
     ].
 !
 
@@ -787,7 +787,7 @@
     col add:10.
     col add:0 beforeIndex:1.
     self assert:(col asArray = #(0 10)).
-    
+
     col := OrderedCollection with:10.
     col add:0 beforeIndex:1.
     self assert:(col asArray = #(0 10)).
@@ -805,7 +805,7 @@
     self assert:(col instVarNamed:'lastIndex') == 2.
     self assert:(col asArray = #(0 10)).
     "
-     self new testOrderedCollection08_addBefore  
+     self new testOrderedCollection08_addBefore
     "
 !
 
@@ -825,7 +825,7 @@
     self assert:(col instVarNamed:'lastIndex') == 4.
     self assert:(col asArray = #(-2 -1 0 10)).
     "
-     self new testOrderedCollection09_addAllBefore  
+     self new testOrderedCollection09_addAllBefore
     "
 ! !
 
@@ -980,13 +980,13 @@
     col add:'b'.
     col add:'c'.
     self assert:( col size == 3 ).
-    self assert:( Array streamContents:[:s | 
-                        col do:[:each | s nextPut:each]
-                  ]
-                ) = #('a' 'b' 'c' ).
+    self assert:( Array streamContents:[:s |
+			col do:[:each | s nextPut:each]
+		  ]
+		) = #('a' 'b' 'c' ).
 
     "
-     self new testOrderedSet02  
+     self new testOrderedSet02
     "
 !
 
@@ -1001,13 +1001,13 @@
     col add:'a'.
     col add:'b'.
     self assert:( col size == 3 ).
-    self assert:( Array streamContents:[:s | 
-                        col do:[:each | s nextPut:each]
-                  ]
-                ) = #('a' 'b' 'c' ).
+    self assert:( Array streamContents:[:s |
+			col do:[:each | s nextPut:each]
+		  ]
+		) = #('a' 'b' 'c' ).
 
     "
-     self new testOrderedSet03  
+     self new testOrderedSet03
     "
 !
 
@@ -1020,13 +1020,13 @@
     col addFirst:'b'.
     col addFirst:'c'.
     self assert:( col size == 3 ).
-    self assert:( Array streamContents:[:s | 
-                        col do:[:each | s nextPut:each]
-                  ]
-                ) = #('c' 'b' 'a' ).
+    self assert:( Array streamContents:[:s |
+			col do:[:each | s nextPut:each]
+		  ]
+		) = #('c' 'b' 'a' ).
 
     "
-     self new testOrderedSet04  
+     self new testOrderedSet04
     "
 !
 
@@ -1042,13 +1042,13 @@
     col add:'b'.
     col add:'c'.
     self assert:( col size == 3 ).
-    self assert:( Array streamContents:[:s | 
-                        col do:[:each | s nextPut:each]
-                  ]
-                ) = #('c' 'b' 'a' ).
+    self assert:( Array streamContents:[:s |
+			col do:[:each | s nextPut:each]
+		  ]
+		) = #('c' 'b' 'a' ).
 
     "
-     self new testOrderedSet05  
+     self new testOrderedSet05
     "
 ! !
 
@@ -1061,12 +1061,12 @@
     s addAll:#('one' 'two' 'three' 'four' 'five').
 
     c := s from:2.
-    
+
     self assert: ( c size == (s size - 1) ).
     1 to:c size do:[:i |
-        self assert: ( (c at:i) == (s at:i+1) ).
+	self assert: ( (c at:i) == (s at:i+1) ).
     ].
-    
+
     c2 := c collect:[:el |el].
     self assert:(c2 size == c size).
     self assert:(c2 = c).
@@ -1074,7 +1074,7 @@
     c2 := c select:[:el |true].
     self assert:(c2 size == c size).
     self assert:(c2 = c).
-    
+
     c2 := c select:[:el | el startsWith:'t'].
     self assert:(c2 size == (s count:[:el | el startsWith:'t' ])).
 
@@ -1086,7 +1086,7 @@
 
     self assert: ( c size == (s size - 1) ).
     1 to:c size do:[:i |
-        self assert: ( (c at:i) == (s at:i+1) ).
+	self assert: ( (c at:i) == (s at:i+1) ).
     ].
 
     c2 := c collect:[:el |el].
@@ -1130,36 +1130,36 @@
 !
 
 testTransliterating
-     self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'b-g' to:'B-G'   ) = 'aBCDEFGhijkl1234567890'. 
-     self assert:( 'abcdefghij-kl1234567890' copyTransliterating:'b\-g' to:'B+G'  ) = 'aBcdefGhij+kl1234567890'.              
-     self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'69' to:'96'     ) = 'abcdefghijkl1234597860'  .  
+     self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'b-g' to:'B-G'   ) = 'aBCDEFGhijkl1234567890'.
+     self assert:( 'abcdefghij-kl1234567890' copyTransliterating:'b\-g' to:'B+G'  ) = 'aBcdefGhij+kl1234567890'.
+     self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'69' to:'96'     ) = 'abcdefghijkl1234597860'  .
      self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'a' to:'b'       ) = 'bbcdefghijkl1234567890'   .
-     self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'aeiou' to:'AEIOU'    ) = 'AbcdEfghIjkl1234567890'.   
-     self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'0-9' to:'QERTYUIOPX' ) = 'abcdefghijklERTYUIOPXQ' .   
+     self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'aeiou' to:'AEIOU'    ) = 'AbcdEfghIjkl1234567890'.
+     self assert:( 'abcdefghijkl1234567890'  copyTransliterating:'0-9' to:'QERTYUIOPX' ) = 'abcdefghijklERTYUIOPXQ' .
 
      self assert:( 'abcdefghijkl1234567890' copyTransliterating:'0-9' to:'A' complement:false squashDuplicates:false )
-                    = 'abcdefghijklAAAAAAAAAA'.
+		    = 'abcdefghijklAAAAAAAAAA'.
 
      self assert:( 'abcdefghijkl1234567890' copyTransliterating:'0-9' to:'A' complement:false squashDuplicates:true )
-                    = 'abcdefghijklA'.
+		    = 'abcdefghijklA'.
 
      self assert:( 'abcdefghijkl1234567890' copyTransliterating:'0-9' to:'*' complement:false squashDuplicates:false )
-                    = 'abcdefghijkl**********'.
+		    = 'abcdefghijkl**********'.
 
      self assert:( 'abcdefghijkl1234567890' copyTransliterating:'0-9' to:'*' complement:true squashDuplicates:false )
-                    = '************1234567890'.
+		    = '************1234567890'.
 
      self assert:( 'abcdefghijkl1234567890' copyTransliterating:'a-zA-Z' to:' ' complement:true squashDuplicates:false )
-                    = 'abcdefghijkl          '.
+		    = 'abcdefghijkl          '.
 
      self assert:( 'abcdefghijkl1234567890' copyTransliterating:'a-zA-Z' to:' ' complement:false squashDuplicates:false )
-                    = '            1234567890'.
+		    = '            1234567890'.
 
      self assert:( 'abcdefghijkl1234567890abcdefghijkl' copyTransliterating:'a-zA-Z' to:'' complement:false squashDuplicates:false )
-                    = '1234567890'.
+		    = '1234567890'.
 
      self assert:( 'abcdefghijkl1234567890abcdefghijkl' copyTransliterating:'a-zA-Z' to:'' complement:true squashDuplicates:false )
-                    = 'abcdefghijklabcdefghijkl'.
+		    = 'abcdefghijklabcdefghijkl'.
 ! !
 
 !CollectionTests methodsFor:'tests-searching'!
@@ -1168,119 +1168,119 @@
     |a|
 
     #(
-        asArray
-        asFloatArray
-        asDoubleArray
-        asHalfFloatArray
-        asSignedWordArray
-        asSignedIntegerArray
-        asSignedLongIntegerArray
+	asArray
+	asFloatArray
+	asDoubleArray
+	asHalfFloatArray
+	asSignedWordArray
+	asSignedIntegerArray
+	asSignedLongIntegerArray
     ) do:[:converter |
-        |empty|
+	|empty|
 
-        empty := #() perform:converter.
-        self should:[ empty min ] raise:Error.
-        self should:[ empty max ] raise:Error.
-        self should:[ empty minMax ] raise:Error.
+	empty := #() perform:converter.
+	self should:[ empty min ] raise:Error.
+	self should:[ empty max ] raise:Error.
+	self should:[ empty minMax ] raise:Error.
 
-        #(
-            (0 0)
-            (1 1)
-            (-1 -1)
-            (0 1)
-            (1 2)
-            (-1 -0)
-            (-1 1)
-            (1 10000)
-            (1 20000)
-            (2 10000)
-            (2 20000)
-            (-1000 1000)
-            (-1000 999)
-        ) pairsDo:[:min :max |
-            a := (min to:max) perform:converter.
-            self assert:(a min) = min.
-            self assert:(a max) = max.
-            self assert:(a minMax) = { min. max }.  
+	#(
+	    (0 0)
+	    (1 1)
+	    (-1 -1)
+	    (0 1)
+	    (1 2)
+	    (-1 -0)
+	    (-1 1)
+	    (1 10000)
+	    (1 20000)
+	    (2 10000)
+	    (2 20000)
+	    (-1000 1000)
+	    (-1000 999)
+	) pairsDo:[:min :max |
+	    a := (min to:max) perform:converter.
+	    self assert:(a min) = min.
+	    self assert:(a max) = max.
+	    self assert:(a minMax) = { min. max }.
 
-            a := a reverse.
-            self assert:(a min) = min.
-            self assert:(a max) = max.
-            self assert:(a minMax) = { min. max }.  
+	    a := a reverse.
+	    self assert:(a min) = min.
+	    self assert:(a max) = max.
+	    self assert:(a minMax) = { min. max }.
 
-            a := a randomShuffle.
-            self assert:(a min) = min.
-            self assert:(a max) = max.
-            self assert:(a minMax) = { min. max }.  
-        ].
+	    a := a randomShuffle.
+	    self assert:(a min) = min.
+	    self assert:(a max) = max.
+	    self assert:(a minMax) = { min. max }.
+	].
     ].
 
     #(
-        asWordArray
-        asIntegerArray
-        asLongIntegerArray
+	asWordArray
+	asIntegerArray
+	asLongIntegerArray
     ) do:[:converter |
-        |empty|
+	|empty|
 
-        empty := #() perform:converter.
-        self should:[ empty min ] raise:Error.
-        self should:[ empty max ] raise:Error.
-        self should:[ empty minMax ] raise:Error.
+	empty := #() perform:converter.
+	self should:[ empty min ] raise:Error.
+	self should:[ empty max ] raise:Error.
+	self should:[ empty minMax ] raise:Error.
 
-        #(
-            (0 0)
-            (1 1)
-            (0 1)
-            (1 2)
-            (1 10000)
-            (1 10001)
-            (2 10000)
-            (2 10001)
-        ) pairsDo:[:min :max |
-            a := (min to:max) perform:converter.
-            self assert:(a min) = min.
-            self assert:(a max) = max.
-            self assert:(a minMax) = { min. max }.  
+	#(
+	    (0 0)
+	    (1 1)
+	    (0 1)
+	    (1 2)
+	    (1 10000)
+	    (1 10001)
+	    (2 10000)
+	    (2 10001)
+	) pairsDo:[:min :max |
+	    a := (min to:max) perform:converter.
+	    self assert:(a min) = min.
+	    self assert:(a max) = max.
+	    self assert:(a minMax) = { min. max }.
 
-            a := a reverse.
-            self assert:(a min) = min.
-            self assert:(a max) = max.
-            self assert:(a minMax) = { min. max }.  
+	    a := a reverse.
+	    self assert:(a min) = min.
+	    self assert:(a max) = max.
+	    self assert:(a minMax) = { min. max }.
 
-            a := a randomShuffle.
-            self assert:(a min) = min.
-            self assert:(a max) = max.
-            self assert:(a minMax) = { min. max }.  
-        ].
+	    a := a randomShuffle.
+	    self assert:(a min) = min.
+	    self assert:(a max) = max.
+	    self assert:(a minMax) = { min. max }.
+	].
     ].
 
     (Array with:Array with:OrderedCollection with:ByteArray with:WordArray with:IntegerArray)
     do:[:cls |
-        a := cls withAll: #(10 20 30 40 50 60 70 80 90 100).
+	a := cls withAll: #(10 20 30 40 50 60 70 80 90 100).
 
-        self assert:(a indexOf:110) == 0.
-        self assert:(a indexOf:10) == 1.
-        self assert:(a indexOf:20) == 2.
-        self assert:(a indexOf:30) == 3.
-        self assert:(a indexOf:40) == 4.
-        self assert:(a indexOf:50) == 5.
-        self assert:(a indexOf:60) == 6.
-        self assert:(a indexOf:70) == 7.
-        self assert:(a indexOf:80) == 8.
-        self assert:(a indexOf:90) == 9.
-        self assert:(a indexOf:100) == 10.
+	self assert:(a indexOf:110) == 0.
+	self assert:(a indexOf:10) == 1.
+	self assert:(a indexOf:20) == 2.
+	self assert:(a indexOf:30) == 3.
+	self assert:(a indexOf:40) == 4.
+	self assert:(a indexOf:50) == 5.
+	self assert:(a indexOf:60) == 6.
+	self assert:(a indexOf:70) == 7.
+	self assert:(a indexOf:80) == 8.
+	self assert:(a indexOf:90) == 9.
+	self assert:(a indexOf:100) == 10.
 
-        self assert:(a identityIndexOf:110) == 0.
-        self assert:(a identityIndexOf:10) == 1.
-        self assert:(a identityIndexOf:20) == 2.
-        self assert:(a identityIndexOf:30) == 3.
-        self assert:(a identityIndexOf:40) == 4.
-        self assert:(a identityIndexOf:50) == 5.
-        self assert:(a identityIndexOf:60) == 6.
-        self assert:(a identityIndexOf:70) == 7.
-        self assert:(a identityIndexOf:80) == 8.
-        self assert:(a identityIndexOf:90) == 9.
-        self assert:(a identityIndexOf:100) == 10.
+	self assert:(a identityIndexOf:110) == 0.
+	self assert:(a identityIndexOf:10) == 1.
+	self assert:(a identityIndexOf:20) == 2.
+	self assert:(a identityIndexOf:30) == 3.
+	self assert:(a identityIndexOf:40) == 4.
+	self assert:(a identityIndexOf:50) == 5.
+	self assert:(a identityIndexOf:60) == 6.
+	self assert:(a identityIndexOf:70) == 7.
+	self assert:(a identityIndexOf:80) == 8.
+	self assert:(a identityIndexOf:90) == 9.
+	self assert:(a identityIndexOf:100) == 10.
     ].
 
     "Created: / 07-10-2011 / 13:11:36 / cg"
@@ -1310,12 +1310,12 @@
     col := SortedCollection new addAll: (100 to: 1 by: -1); yourself.
     last := nil.
     errs := col inject: 0 into:
-            [ :totIn :n | |totOut|
+	    [ :totIn :n | |totOut|
 
-            totOut := totIn.
-            last notNil ifTrue: [ last > n ifTrue: [ totOut := totOut + 1 ] ].
-            last := n.
-            totOut ].
+	    totOut := totIn.
+	    last notNil ifTrue: [ last > n ifTrue: [ totOut := totOut + 1 ] ].
+	    last := n.
+	    totOut ].
     self should: [ errs = 0 ]
 
     "
@@ -1342,13 +1342,13 @@
     lastTestData := nil.
 
     errs := col inject: 0 into:
-            [ :totIn :aSortTestData | |totOut|
-            totOut := totIn.
-            lastTestData notNil ifTrue:
-                    [ lastTestData value = aSortTestData value ifTrue:
-                            [ lastTestData order > aSortTestData order ifTrue: [ totOut := totOut + 1 ] ] ].
-            lastTestData := aSortTestData.
-            totOut ].
+	    [ :totIn :aSortTestData | |totOut|
+	    totOut := totIn.
+	    lastTestData notNil ifTrue:
+		    [ lastTestData value = aSortTestData value ifTrue:
+			    [ lastTestData order > aSortTestData order ifTrue: [ totOut := totOut + 1 ] ] ].
+	    lastTestData := aSortTestData.
+	    totOut ].
     self should: [ errs = 0 ]
 
     "
@@ -1373,13 +1373,13 @@
     lastTestData := nil.
 
     errs := col inject: 0 into:
-            [ :totIn :aSortTestData | |totOut|
-            totOut := totIn.
-            lastTestData notNil ifTrue:
-                    [ lastTestData value = aSortTestData value ifTrue:
-                            [ lastTestData order > aSortTestData order ifTrue: [ totOut := totOut + 1 ] ] ].
-            lastTestData := aSortTestData.
-            totOut ].
+	    [ :totIn :aSortTestData | |totOut|
+	    totOut := totIn.
+	    lastTestData notNil ifTrue:
+		    [ lastTestData value = aSortTestData value ifTrue:
+			    [ lastTestData order > aSortTestData order ifTrue: [ totOut := totOut + 1 ] ] ].
+	    lastTestData := aSortTestData.
+	    totOut ].
     self should: [ errs = 0 ]
 
 "
@@ -1390,31 +1390,31 @@
 testSortedCollectionQueries
     "test a SortedCollection, where only a single attribute is used for sorting.
      #include: failed before 2015-06-24"
-    
+
     |collection|
 
     collection := SortedCollection sortBlock:[:a :b | a key < b key ].
-    $a to:$z do:[:l | 
-        1 to:100 do:[:i | 
-            collection add:(Association key:l value:i)
-        ].
+    $a to:$z do:[:l |
+	1 to:100 do:[:i |
+	    collection add:(Association key:l value:i)
+	].
     ].
-     
+
     "/ make startIndex > 1 and endIndex < size
-    
+
     collection
-        removeFirst;
-        removeLast.
-    collection 
-        keysAndValuesDo:[:eachIndex :eachElement | 
-            self assert:(collection detect:[:el | el = eachElement ]) notNil.
-            self assert:(collection includes:eachElement).
-            self assert:(collection indexOf:eachElement) = eachIndex.
-            self assert:(collection occurrencesOf:eachElement) = 1.
-            self 
-                assert:(collection 
-                        includes:(eachElement copy value:(eachElement value + 1000))) not.
-        ].
+	removeFirst;
+	removeLast.
+    collection
+	keysAndValuesDo:[:eachIndex :eachElement |
+	    self assert:(collection detect:[:el | el = eachElement ]) notNil.
+	    self assert:(collection includes:eachElement).
+	    self assert:(collection indexOf:eachElement) = eachIndex.
+	    self assert:(collection occurrencesOf:eachElement) = 1.
+	    self
+		assert:(collection
+			includes:(eachElement copy value:(eachElement value + 1000))) not.
+	].
 ! !
 
 !CollectionTests methodsFor:'tests-squeak'!
@@ -1455,41 +1455,41 @@
 !CollectionTests::SortTestData methodsFor:'accessing'!
 
 value
-        "Answer the value of the receiver's ''value'' instance variable."
+	"Answer the value of the receiver's ''value'' instance variable."
 
-        ^value
+	^value
 !
 
 value: anObject
-        "Set the value of the receiver's ''value'' instance variable to the argument, anObject."
+	"Set the value of the receiver's ''value'' instance variable to the argument, anObject."
 
-        value := anObject
+	value := anObject
 ! !
 
 !CollectionTests::SortTestData methodsFor:'order'!
 
 order
-        "Answer the value of the receiver's ''order'' instance variable."
+	"Answer the value of the receiver's ''order'' instance variable."
 
-        ^order
+	^order
 !
 
 order: anObject
-        "Set the value of the receiver's ''order'' instance variable to the argument, anObject."
+	"Set the value of the receiver's ''order'' instance variable to the argument, anObject."
 
-        order := anObject
+	order := anObject
 ! !
 
 !CollectionTests::SortTestData methodsFor:'printing & storing'!
 
 printOn: aStream
-        super printOn: aStream.
-        aStream
-                nextPutAll: '(value: ';
-                nextPutAll: value printString;
-                nextPutAll: ' order: ';
-                nextPutAll: order printString;
-                nextPut: $)
+	super printOn: aStream.
+	aStream
+		nextPutAll: '(value: ';
+		nextPutAll: value printString;
+		nextPutAll: ' order: ';
+		nextPutAll: order printString;
+		nextPut: $)
 ! !
 
 !CollectionTests class methodsFor:'documentation'!