RegressionTests__StringTests.st
changeset 2569 9b7a08d2261c
parent 2567 bf0f6e311a5d
child 2570 d62760a8ac9a
--- a/RegressionTests__StringTests.st	Mon Feb 24 00:25:08 2020 +0100
+++ b/RegressionTests__StringTests.st	Mon Feb 24 14:27:58 2020 +0100
@@ -33,15 +33,15 @@
     |str s0 s1 s2 s3 s4 t|
 
     0 to:33 do:[:l |
-        str := aStringClass new:l.
-        str atAllPut:(Character space).
-        self assert:( str isBlank ).
+	str := aStringClass new:l.
+	str atAllPut:(Character space).
+	self assert:( str isBlank ).
 
-        1 to:l do:[:pos |
-            str at:pos put:$a.
-            self assert:( str isBlank not ).
-            str at:pos put:(Character space).
-        ].
+	1 to:l do:[:pos |
+	    str at:pos put:$a.
+	    self assert:( str isBlank not ).
+	    str at:pos put:(Character space).
+	].
     ].
 
     s0 := aStringClass new:0.
@@ -122,7 +122,7 @@
     self assert:(s1 includesAny:'aebc').
     self assert:(s1 includesAny:'abec').
     self assert:(s1 includesAny:'abcde').
-                                                  " 12345678901234567890 "
+						  " 12345678901234567890 "
     s3 := (aStringClass new:20) replaceFrom:1 with:'12 45,78;01.34-67+90'.
     t := s3 asCollectionOfSubstringsSeparatedBy:$,.
     self assert:(t size = 2).
@@ -165,48 +165,48 @@
     haystack replaceFrom:(haystack size-toBeFoundAtEnd size) with:toBeFoundAtEnd.
 
     #(
-        $0
-        '0'
-        '01'
-        '012'
-        '0123'
-        '01234'
-        '012345'
-        '0123456'
-        '01234567'
-        '012345678'
-        '0123456789'
-        '01234567890123456789'
-        '0123456789012345678901234567890123456789'
-        '01234567890123456789012345678901234567890123456789'
-        '0123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789'
+	$0
+	'0'
+	'01'
+	'012'
+	'0123'
+	'01234'
+	'012345'
+	'0123456'
+	'01234567'
+	'012345678'
+	'0123456789'
+	'01234567890123456789'
+	'0123456789012345678901234567890123456789'
+	'01234567890123456789012345678901234567890123456789'
+	'0123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789'
     ) do:[:needle |
-        |micros i|
+	|micros i|
 
-        needle isCharacter ifTrue:[
-            micros := Time microsecondsToRun:[
-                    1000 timesRepeat:[
-                        haystack indexOf:needle startingAt:1
-                    ].
-                 ].
-            i := haystack indexOf:needle startingAt:1
-        ] ifFalse:[
-            micros := Time microsecondsToRun:[
-                    1000 timesRepeat:[
-                        haystack indexOfSubCollection:needle startingAt:1 ifAbsent:0 caseSensitive:true
+	needle isCharacter ifTrue:[
+	    micros := Time microsecondsToRun:[
+		    1000 timesRepeat:[
+			haystack indexOf:needle startingAt:1
+		    ].
+		 ].
+	    i := haystack indexOf:needle startingAt:1
+	] ifFalse:[
+	    micros := Time microsecondsToRun:[
+		    1000 timesRepeat:[
+			haystack indexOfSubCollection:needle startingAt:1 ifAbsent:0 caseSensitive:true
 
-                    ].
-                 ].
-            i := haystack indexOfSubCollection:needle startingAt:1 ifAbsent:(haystack size) caseSensitive:true.
-        ].
+		    ].
+		 ].
+	    i := haystack indexOfSubCollection:needle startingAt:1 ifAbsent:(haystack size) caseSensitive:true.
+	].
 
-        Transcript showCR:'size %1: t=%2 (%3 chars/second)' 
-                     with:(needle isCharacter ifTrue:[1] ifFalse:[needle size])
-                     with:(TimeDuration microseconds:micros)
-                     with:(UnitConverter 
-                            unitStringFor:((i*1000000.0) / micros )
-                            scale:1000 rounded:true
-                            unitStrings:#('' 'k' 'M' 'G' 'T' 'P' 'E' )).
+	Transcript showCR:'size %1: t=%2 (%3 chars/second)'
+		     with:(needle isCharacter ifTrue:[1] ifFalse:[needle size])
+		     with:(TimeDuration microseconds:micros)
+		     with:(UnitConverter
+			    unitStringFor:((i*1000000.0) / micros )
+			    scale:1000 rounded:true
+			    unitStrings:#('' 'k' 'M' 'G' 'T' 'P' 'E' )).
     ].
 !
 
@@ -325,7 +325,7 @@
     self assert:((u at:3) == $c).
     self assert:((u at:4) == $d).
     self assert:((u at:5) == $e).
-    
+
     "
      self new test03a_unicode16
     "
@@ -393,7 +393,7 @@
     self assert:((u at:3) == $c).
     self assert:((u at:4) == $d).
     self assert:((u at:5) == $e).
-    
+
     "
      self new test03b_unicode32
     "
@@ -413,13 +413,13 @@
     self assert:(u8 = u32).
     self assert:(u16 = u8).
     self assert:(u8 = u16).
-    
+
     self assert:(u32 asDenseUnicodeString = u8).
     self assert:(u32 asDenseUnicodeString class == String).
     self assert:(u16 asDenseUnicodeString = u8).
     self assert:(u16 asDenseUnicodeString class == String).
     self assert:(u8 asDenseUnicodeString == u8).
-    
+
     "
      self new test03c_unicodeStrings
     "
@@ -588,23 +588,23 @@
     self assert:('A' sameAs:'1') not.
 
     1 to:20 do:[:len |
-        |s1 s2|
+	|s1 s2|
 
-        s1 := ($a to:($a + len - 1)) asString.
-        s2 := s1 copy.
-        1 to:len do:[:idx |
-            s2 at:idx put:(s2 at:idx) asUppercase.
-            self assert:(s1 sameAs:s2).
-        ].
+	s1 := ($a to:($a + len - 1)) asString.
+	s2 := s1 copy.
+	1 to:len do:[:idx |
+	    s2 at:idx put:(s2 at:idx) asUppercase.
+	    self assert:(s1 sameAs:s2).
+	].
     ].
-    
+
     self assert:('Ä' sameAs:'ä').
     self assert:('Ä' sameAs:'ä').
     self assert:('ß' sameAs:'ÿ') not.
     self assert:('Ÿ' sameAs:'ÿ'). "/ single byte char ws. wide char
     self assert:('Ÿ' sameAs:'Ÿ'). "/ single byte char ws. wide char
     self assert:('ÿ' sameAs:'ÿ'). "/ single byte char ws. wide char
-    
+
     "
      self new test13_startsWithEndsWithSameAs
     "
@@ -752,7 +752,7 @@
     self assert:(i == 7).
     i := 'hello world' indexOfString:'world' startingAt:8.
     self assert:(i == 0).
-    
+
     i := 'hello wOrLd' indexOfString:'world' startingAt:1.
     self assert:(i == 0).
 
@@ -859,7 +859,7 @@
     self assert:(i == 0).
     i := 'hello world' indexOfSubCollection:'world' startingAt:8 ifAbsent:0 caseSensitive:true.
     self assert:(i == 0).
-    
+
     i := 'hello wOrLd' indexOfSubCollection:'world' startingAt:1 ifAbsent:0 caseSensitive:true.
     self assert:(i == 0).
     i := 'hello wOrLd' indexOfSubCollection:'world' startingAt:1 ifAbsent:0 caseSensitive:false.
@@ -890,33 +890,33 @@
     n := '' occurrencesOfString:'aa'.
     self assert:(n == 0).
 
-    n := 'a' occurrencesOfString:'aa'.  
+    n := 'a' occurrencesOfString:'aa'.
     self assert:(n == 0).
 
-    n := 'aa' occurrencesOfString:'aa'.  
+    n := 'aa' occurrencesOfString:'aa'.
     self assert:(n == 1).
 
-    n := ' aa ' occurrencesOfString:'aa'.  
+    n := ' aa ' occurrencesOfString:'aa'.
     self assert:(n == 1).
 
-    n := ' aa a' occurrencesOfString:'aa'.  
+    n := ' aa a' occurrencesOfString:'aa'.
     self assert:(n == 1).
 
-    n := ' aaaa' occurrencesOfString:'aa'.  
+    n := ' aaaa' occurrencesOfString:'aa'.
     self assert:(n == 2).
 
-    n := ' aa aa ' occurrencesOfString:'aa'.  
+    n := ' aa aa ' occurrencesOfString:'aa'.
     self assert:(n == 2).
 
-    n := ' aa bb ab ba aa ab' occurrencesOfString:'aa'.  
+    n := ' aa bb ab ba aa ab' occurrencesOfString:'aa'.
     self assert:(n == 2).
 
-    n := ' aa bb cc aa bb cc aa bb ' occurrencesOfString:'aa'.  
+    n := ' aa bb cc aa bb cc aa bb ' occurrencesOfString:'aa'.
     self assert:(n == 3).
 
-    n := ' aa bb cc aA bb cc Aa bb ' occurrencesOfString:'aa'.  
+    n := ' aa bb cc aA bb cc Aa bb ' occurrencesOfString:'aa'.
     self assert:(n == 1).
-    n := ' aa bb cc aA bb cc Aa bb ' occurrencesOfString:'aa' caseSensitive:false.  
+    n := ' aa bb cc aA bb cc Aa bb ' occurrencesOfString:'aa' caseSensitive:false.
     self assert:(n == 3).
 
     "
@@ -1000,14 +1000,14 @@
     |s|
 
     1 to:20 do:[:na |
-        s := (String new:na withAll:$a),'bla bla 1234'.
-        self assert:( s includesAny:'12').
-        self assert:( s includesAny:'21').
-        self assert:( s includesAny:'15').
-        self assert:( s includesAny:'51').
-        self assert:( s includesAny:'45').
-        self assert:( s includesAny:'54').
-        self assert:( s includesAny:'56') not.
+	s := (String new:na withAll:$a),'bla bla 1234'.
+	self assert:( s includesAny:'12').
+	self assert:( s includesAny:'21').
+	self assert:( s includesAny:'15').
+	self assert:( s includesAny:'51').
+	self assert:( s includesAny:'45').
+	self assert:( s includesAny:'54').
+	self assert:( s includesAny:'56') not.
     ].
 
     "
@@ -1022,7 +1022,7 @@
     self assert:('he*llo' includesMatchCharacters).
     self assert:('h[eE]llo' includesMatchCharacters).
     self assert:('h#llo' includesMatchCharacters).
-    
+
     "
      self new test42b_includesMatchCharacters
     "
@@ -1063,7 +1063,7 @@
     self assert:(' he llo ' includesSeparator).
     self assert:(c'h\nllo' includesSeparator).
     self assert:(c'h\tllo' includesSeparator).
-    
+
     "
      self new test42c_includesSeparator
     "
@@ -1113,8 +1113,8 @@
 
     s := 'Some Sample Generators (74035660-d1f6-11df-9ab3-00ff7b08316c)'.
     1 to:s size do:[:start |
-        i := s indexOf:$- startingAt:start.
-        self assert:(i == 0 or:[ i >= start]).
+	i := s indexOf:$- startingAt:start.
+	self assert:(i == 0 or:[ i >= start]).
     ].
     "/             12345678901
     self assert:( 'hello world' indexOf:$0 startingAt:1 ) == 0.
@@ -1427,18 +1427,18 @@
     | tester |
 
     tester := [:s|
-        |sHash u16Hash u32Hash|
+	|sHash u16Hash u32Hash|
 
-        sHash := s hash.
-        u16Hash := s asUnicode16String hash.
-        u32Hash := s asUnicode32String hash.
+	sHash := s hash.
+	u16Hash := s asUnicode16String hash.
+	u32Hash := s asUnicode32String hash.
 
-        self assert: sHash == u16Hash
-             description: ('String and Unicode16String hashes differ on "%1" (%2)'
-                                bindWith:s with:s class name).
-        self assert: sHash == u32Hash
-             description: ('String and Unicode32String hashes differ on "%1" (%2)'
-                                bindWith:s with:s class name)
+	self assert: sHash == u16Hash
+	     description: ('String and Unicode16String hashes differ on "%1" (%2)'
+				bindWith:s with:s class name).
+	self assert: sHash == u32Hash
+	     description: ('String and Unicode32String hashes differ on "%1" (%2)'
+				bindWith:s with:s class name)
     ].
 
     tester value:'a'.
@@ -1508,24 +1508,24 @@
     | tester |
 
     "/ self skip:'takes long'.
-    
+
     tester := [:s|
-        |sHash u8Hash u16Hash u32Hash|
+	|sHash u8Hash u16Hash u32Hash|
 
-        sHash := s hash.
-        u8Hash := s asString hash.
-        u16Hash := s asUnicode16String hash.
-        u32Hash := s asUnicode32String hash.
+	sHash := s hash.
+	u8Hash := s asString hash.
+	u16Hash := s asUnicode16String hash.
+	u32Hash := s asUnicode32String hash.
 
-        self assert: sHash == u8Hash
-             description: ('Symbol and String hashes differ on "%1" (%2)'
-                                bindWith:s with:s class name).
-        self assert: sHash == u16Hash
-             description: ('Symbol and Unicode16String hashes differ on "%1" (%2)'
-                                bindWith:s with:s class name).
-        self assert: sHash == u32Hash
-             description: ('Symbol and Unicode32String hashes differ on "%1" (%2)'
-                                bindWith:s with:s class name)
+	self assert: sHash == u8Hash
+	     description: ('Symbol and String hashes differ on "%1" (%2)'
+				bindWith:s with:s class name).
+	self assert: sHash == u16Hash
+	     description: ('Symbol and Unicode16String hashes differ on "%1" (%2)'
+				bindWith:s with:s class name).
+	self assert: sHash == u32Hash
+	     description: ('Symbol and Unicode32String hashes differ on "%1" (%2)'
+				bindWith:s with:s class name)
     ].
 
     "/ String allInstancesDo:[:each| tester value:each].
@@ -1536,7 +1536,7 @@
 
 test61_hash
     "all string-representations must hash equal"
-    
+
     | string8 string16 string32 |
 
     string8 := 'sun/nio/cs/UTF_8.class'.
@@ -1555,22 +1555,22 @@
     |strA strB|
 
     0 to:32 do:[:szA |
-        0 to:32 do:[:szB |
-            |szAB|
+	0 to:32 do:[:szB |
+	    |szAB|
 
-            strA := String new:szA withAll:$a.
-            strB := String new:szB withAll:$b.
-            szAB := szA + szB.
-            self assert:(szA = strA size).
-            self assert:(szB = strB size).
-            "/ why repeat ??? - to check GC???
-            1 "10000" timesRepeat:[
-                |strAB|
+	    strA := String new:szA withAll:$a.
+	    strB := String new:szB withAll:$b.
+	    szAB := szA + szB.
+	    self assert:(szA = strA size).
+	    self assert:(szB = strB size).
+	    "/ why repeat ??? - to check GC???
+	    1 "10000" timesRepeat:[
+		|strAB|
 
-                strAB := strA , strB.
-                self assert:(szAB == strAB size).
-            ]
-        ]
+		strAB := strA , strB.
+		self assert:(szAB == strAB size).
+	    ]
+	]
     ].
 
     strA := strB := ''.
@@ -1590,7 +1590,7 @@
     self assert:('hello',123) = 'hello123'.
     self assert:('hello' asUnicode16String,123) = 'hello123' asUnicode16String.
     self assert:('hello' asUnicode32String,123) = 'hello123' asUnicode32String.
-    
+
     "/ concatenating other things
     self assert:('hello',,123) = c'hello\n123'.
     self assert:('hello' asUnicode16String,,123) = c'hello\n123' asUnicode16String.
@@ -1632,28 +1632,28 @@
     |strA strB strC|
 
     0 to:32 do:[:szA |
-        0 to:32 do:[:szB |
-            0 to:32 do:[:szC |
-                |szABC|
-                strA := String new:szA withAll:$a.
-                strB := String new:szB withAll:$b.
-                strC := String new:szC withAll:$c.
+	0 to:32 do:[:szB |
+	    0 to:32 do:[:szC |
+		|szABC|
+		strA := String new:szA withAll:$a.
+		strB := String new:szB withAll:$b.
+		strC := String new:szC withAll:$c.
 
-                szABC := szA + szB + szC.
-                self assert:(szA = strA size).
-                self assert:(szB = strB size).
-                self assert:(szC = strC size).
+		szABC := szA + szB + szC.
+		self assert:(szA = strA size).
+		self assert:(szB = strB size).
+		self assert:(szC = strC size).
 
-                "/ why repeat? to test GC???
-                1 "300" timesRepeat:[
-                    |strABC|
+		"/ why repeat? to test GC???
+		1 "300" timesRepeat:[
+		    |strABC|
 
-                    strABC := strA concatenate:strB and:strC.
+		    strABC := strA concatenate:strB and:strC.
 
-                    self assert:(szABC == strABC size).
-                ]
-            ]
-        ]
+		    self assert:(szABC == strABC size).
+		]
+	    ]
+	]
     ].
     strA := strB := strC := ''.
     self assert: ((strA concatenate:strB and:strC) = '').
@@ -1680,33 +1680,33 @@
     |strA strB strC strD|
 
     0 to:32 do:[:szA |
-        strA := String new:szA withAll:$a.
-        self assert:(szA = strA size).
-        0 to:32 do:[:szB |
-            strB := String new:szB withAll:$b.
-            self assert:(szB = strB size).
-            0 to:32 do:[:szC |
-                strC := String new:szC withAll:$c.
-                self assert:(szC = strC size).
-                0 to:32 do:[:szD |
-                    |szABCD|
-                    strD := String new:szD withAll:$d.
+	strA := String new:szA withAll:$a.
+	self assert:(szA = strA size).
+	0 to:32 do:[:szB |
+	    strB := String new:szB withAll:$b.
+	    self assert:(szB = strB size).
+	    0 to:32 do:[:szC |
+		strC := String new:szC withAll:$c.
+		self assert:(szC = strC size).
+		0 to:32 do:[:szD |
+		    |szABCD|
+		    strD := String new:szD withAll:$d.
 
-                    szABCD := szA + szB + szC + szD.
+		    szABCD := szA + szB + szC + szD.
 
-                    self assert:(szD = strD size).
+		    self assert:(szD = strD size).
 
-                    "/ why repeat???
-                    1 "5" timesRepeat:[
-                        |strABCD|
+		    "/ why repeat???
+		    1 "5" timesRepeat:[
+			|strABCD|
 
-                        strABCD := strA concatenate:strB and:strC and:strD.
+			strABCD := strA concatenate:strB and:strC and:strD.
 
-                        self assert:(szABCD == strABCD size).
-                    ]
-                ]
-            ]
-        ]
+			self assert:(szABCD == strABCD size).
+		    ]
+		]
+	    ]
+	]
     ].
 
     strA := strB := strC := strD := ''.
@@ -1857,33 +1857,33 @@
     rslt := 'A%%1B%2C%' expandPlaceholdersWith:#(10 20 30).
     self assert:(rslt = 'A%1B20C%').
 
-    
+
     rslt := 'A%aB%bC' expandPlaceholdersWith:(Dictionary withKeys:#(a b c)
-                                                         andValues:#(10 20 30)).
+							 andValues:#(10 20 30)).
     self assert:(rslt = 'A10B20C').
 
     "/ not expanded, if not found
     rslt := 'A%aB%bC' expandPlaceholdersWith:(Dictionary withKeys:#(aa bb cc)
-                                                         andValues:#(10 20 30)).
+							 andValues:#(10 20 30)).
     self assert:(rslt = 'A%aB%bC').
 
     rslt := 'A%aaB%bbC' expandPlaceholdersWith:(Dictionary withKeys:#(aa bb cc)
-                                                         andValues:#(10 20 30)).
+							 andValues:#(10 20 30)).
     self assert:(rslt = 'A%aaB%bbC').
 
     rslt := 'A%(aa)B%(bb)C' expandPlaceholdersWith:(Dictionary withKeys:#(aa bb cc)
-                                                         andValues:#(10 20 30)).
+							 andValues:#(10 20 30)).
     self assert:(rslt = 'A10B20C').
 
-    "/ allowing non-parenthized 
+    "/ allowing non-parenthized
     rslt := String streamContents:[:s |
-                'A%aa,B%bb,C' 
-                        expandPlaceholders:$%
-                        with:(Dictionary withKeys:#(aa bb cc) andValues:#(10 20 30))
-                        ignoreNumericEscapes:false 
-                        requireParentheses:false
-                        on:s.
-            ].
+		'A%aa,B%bb,C'
+			expandPlaceholders:$%
+			with:(Dictionary withKeys:#(aa bb cc) andValues:#(10 20 30))
+			ignoreNumericEscapes:false
+			requireParentheses:false
+			on:s.
+	    ].
     self assert:(rslt = 'A10,B20,C').
 
     "Created: / 02-04-2019 / 11:00:08 / Claus Gittinger"
@@ -1892,9 +1892,9 @@
 test82b_expanding
     | rslt |
 
-    rslt := 'hello' copyExpanding:(Dictionary 
-                                        withKeys:{$h . $e . $o} 
-                                        andValues:{'HH' . 'EE' . $O }).
+    rslt := 'hello' copyExpanding:(Dictionary
+					withKeys:{$h . $e . $o}
+					andValues:{'HH' . 'EE' . $O }).
     self assert:(rslt = 'HHEEllO').
 
     rslt := 'he%2llo%1' % { 123 . 456 }.
@@ -1907,130 +1907,130 @@
     | rslt |
 
     rslt := '%1-%2-%3'
-            expandPlaceholders:$$
-            with:{10 . 20 . 30}
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$$
+	    with:{10 . 20 . 30}
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '%1-%2-%3').
 
     rslt := '$$rev'
-            expandPlaceholders:$$
-            with:{10 . 20 . 30}
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$$
+	    with:{10 . 20 . 30}
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '$rev').
 
     rslt := '$$rev'
-            expandPlaceholders:$$
-            with:(Dictionary withKeysAndValues:{ 'rev' . '1234'})
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$$
+	    with:(Dictionary withKeysAndValues:{ 'rev' . '1234'})
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '$rev').
 
     rslt := '$rev'
-            expandPlaceholders:$$
-            with:{10 . 20 . 30}
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$$
+	    with:{10 . 20 . 30}
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '$rev').
 
     rslt := '$rev'
-            expandPlaceholders:$$
-            with:(Dictionary withKeysAndValues:{ 'rev' . '1234'})
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$$
+	    with:(Dictionary withKeysAndValues:{ 'rev' . '1234'})
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '1234').
 
     rslt := '%1-%2-%3'
-            expandPlaceholders:$%
-            with:{10 . 20 . 30}
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:{10 . 20 . 30}
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '10-20-30').
 
     rslt := '%1-%2-%3'
-            expandPlaceholders:$%
-            with:{10 . 20 . 30}
-            ignoreNumericEscapes:true
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:{10 . 20 . 30}
+	    ignoreNumericEscapes:true
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '%1-%2-%3').
 
     rslt := '%1%<cr>%2%<cr>%3'
-            expandPlaceholders:$%
-            with:{10 . 20 . 30}
-            ignoreNumericEscapes:true
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:{10 . 20 . 30}
+	    ignoreNumericEscapes:true
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = c'%1\n%2\n%3').
 
     rslt := '%1%<cr>%2%<cr>%3'
-            expandPlaceholders:$%
-            with:{10 . 20 . 30}
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:{10 . 20 . 30}
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = c'10\n20\n30').
 
     rslt := '%1%<cr>%2%<cr>%3'
-            expandPlaceholders:$%
-            with:{10 . 20 . 30}
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:true
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:{10 . 20 . 30}
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:true
+	    requireParentheses:false.
     self assert:(rslt = '10%<cr>20%<cr>30').
 
     rslt := '%1 %(a) %(1) %(b)'
-            expandPlaceholders:$%
-            with:(Dictionary withKeysAndValues:{ 'a' . 'AAA' . 'b' . 'BBB' })
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:true
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:(Dictionary withKeysAndValues:{ 'a' . 'AAA' . 'b' . 'BBB' })
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:true
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = ' %(a)  %(b)').
 
     rslt := '%1 %(a) %(1) %(b)'
-            expandPlaceholders:$%
-            with:(Dictionary withKeysAndValues:{ 'a' . 'AAA' . 'b' . 'BBB' })
-            ignoreNumericEscapes:true
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:(Dictionary withKeysAndValues:{ 'a' . 'AAA' . 'b' . 'BBB' })
+	    ignoreNumericEscapes:true
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '%1 AAA %(1) BBB').
 
     rslt := '%1 %a %(1) %b'
-            expandPlaceholders:$%
-            with:(Dictionary withKeysAndValues:{ 'a' . 'AAA' . 'b' . 'BBB' })
-            ignoreNumericEscapes:true
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:(Dictionary withKeysAndValues:{ 'a' . 'AAA' . 'b' . 'BBB' })
+	    ignoreNumericEscapes:true
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '%1 AAA %(1) BBB').
 
 
     rslt := '%1 %aa %(1) %bb'
-            expandPlaceholders:$%
-            with:(Dictionary withKeysAndValues:{ 'a' . 'AAA' . 'b' . 'BBB' })
-            ignoreNumericEscapes:true
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:true.
+	    expandPlaceholders:$%
+	    with:(Dictionary withKeysAndValues:{ 'a' . 'AAA' . 'b' . 'BBB' })
+	    ignoreNumericEscapes:true
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:true.
     self assert:(rslt = '%1 AAAa %(1) BBBb').
 !
 
@@ -2040,51 +2040,51 @@
     | rslt |
 
     rslt := '%1-%2-%3'
-            expandPlaceholders:$%
-            with:{10 . 20 }
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:{10 . 20 }
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '10-20-').
 
     "/ stupid backward compatibiliy!!
     rslt := '%a-%b-%c'
-            expandPlaceholders:$%
-            with:(Dictionary withKeys:#('a' 'b') andValues:#(10 20 ))
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:(Dictionary withKeys:#('a' 'b') andValues:#(10 20 ))
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '10-20-%c').
 
     rslt := '%(a)-%(b)-%(c)'
-            expandPlaceholders:$%
-            with:(Dictionary withKeys:#('a' 'b') andValues:#(10 20 ))
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:(Dictionary withKeys:#('a' 'b') andValues:#(10 20 ))
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = '10-20-').
 
     rslt := '%(a)-%(b)-%(c)'
-            expandPlaceholders:$%
-            with:(Dictionary withKeys:#('a' 'b') andValues:#(10 20 ))
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false
-            ifKeyAbsent:[:str :var | str].
+	    expandPlaceholders:$%
+	    with:(Dictionary withKeys:#('a' 'b') andValues:#(10 20 ))
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false
+	    ifKeyAbsent:[:str :var | str].
     self assert:(rslt = '10-20-%(c)').
 
     rslt := '%(a)-%(b)-%(abc)'
-            expandPlaceholders:$%
-            with:(Dictionary withKeys:#('a' 'b') andValues:#(10 20 ))
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false
-            ifKeyAbsent:[:str :var | str].
+	    expandPlaceholders:$%
+	    with:(Dictionary withKeys:#('a' 'b') andValues:#(10 20 ))
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false
+	    ifKeyAbsent:[:str :var | str].
     self assert:(rslt = '10-20-%(abc)').
 !
 
@@ -2092,21 +2092,21 @@
     | rslt |
 
     rslt := 'abc%<tab>def'
-            expandPlaceholders:$%
-            with:nil
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:nil
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = ('abc',Character tab,'def')).
 
     rslt := 'abc%<crlf>def'
-            expandPlaceholders:$%
-            with:nil
-            ignoreNumericEscapes:false
-            ignoreNonNumericEscapes:false
-            ignoreSpecialEscapes:false
-            requireParentheses:false.
+	    expandPlaceholders:$%
+	    with:nil
+	    ignoreNumericEscapes:false
+	    ignoreNonNumericEscapes:false
+	    ignoreSpecialEscapes:false
+	    requireParentheses:false.
     self assert:(rslt = ('abc',String crlf,'def')).
 
     rslt := 'abc%<crlf>def' with:nil.
@@ -2129,7 +2129,7 @@
     self assert:(rslt = '').
     rslt := '%9' bindWith:'aaa'.
     self assert:(rslt = '').
-    rslt := '%9' bindWithArguments:#(a1 b2 c3 d4 e5 f6 g7 h8 i9).  
+    rslt := '%9' bindWithArguments:#(a1 b2 c3 d4 e5 f6 g7 h8 i9).
     self assert:(rslt = 'i9').
     rslt := '%1x' bindWithArguments:#(a1 b2 c3 d4 e5 f6 g7 h8 i9 j10).
     self assert:(rslt = 'a1x').
@@ -2146,14 +2146,14 @@
     self assert:(rslt = 'hello x1x').
 
     args := Dictionary new
-                at:'year' put:'yyyy';
-                at:'mon' put:'mmm';
-                at:'day' put:'dd';
-                at:'h' put:'HH';
-                at:'m' put:'MM';
-                at:'s' put:'SS';
-                at:'i' put:'II';
-                yourself.
+		at:'year' put:'yyyy';
+		at:'mon' put:'mmm';
+		at:'day' put:'dd';
+		at:'h' put:'HH';
+		at:'m' put:'MM';
+		at:'s' put:'SS';
+		at:'i' put:'II';
+		yourself.
 
     rslt := '%(year)-%(mon)-%(day) %h:%m:%s.%i' bindWithArguments:args.
     self assert:(rslt = 'yyyy-mmm-dd HH:MM:SS.II').
@@ -2191,7 +2191,7 @@
 
     rslt := '' paddedTo:2 with:$-.
     self assert:(rslt = '--').
-    
+
     rslt := 'foo' leftPaddedTo:10.
     self assert:(rslt = '       foo').
 
@@ -2239,30 +2239,30 @@
     "/ verify that our printf generates the same string as the system-printf.
 
     #(
-        '%s'       ''           ''  
-        '%s'       'abc'        'abc'  
-        'x%s'      ''           'x'  
-        'x%s'      'abc'        'xabc'  
-        '%sx'      ''           'x'  
-        '%sx'      'abc'        'abcx'  
-        'x%sx'     ''           'xx'  
-        'x%sx'     'abc'        'xabcx'  
-        '%6s'      'abc'        '   abc'  
-        '%-6s'     'abc'        'abc   '  
-     "/   '%06s'     'abc'        '000abc'  
-     "/   '%-06s'    'abc'        'abc000' 
+	'%s'       ''           ''
+	'%s'       'abc'        'abc'
+	'x%s'      ''           'x'
+	'x%s'      'abc'        'xabc'
+	'%sx'      ''           'x'
+	'%sx'      'abc'        'abcx'
+	'x%sx'     ''           'xx'
+	'x%sx'     'abc'        'xabcx'
+	'%6s'      'abc'        '   abc'
+	'%-6s'     'abc'        'abc   '
+     "/   '%06s'     'abc'        '000abc'
+     "/   '%-06s'    'abc'        'abc000'
 
-        '%.3s'     'abcdef'     'abc'  
-        '%6.3s'    'abcdef'     '   abc'  
-        '%-6.3s'   'abcdef'     'abc   '  
+	'%.3s'     'abcdef'     'abc'
+	'%6.3s'    'abcdef'     '   abc'
+	'%-6.3s'   'abcdef'     'abc   '
 
     ) inGroupsOf:3 do:[:fmt :val :expected|
-        |printfGenerated stxGenerated|
+	|printfGenerated stxGenerated|
 
-        printfGenerated := val printfPrintString:fmt.
-        stxGenerated := PrintfScanf printf:fmt argument:val.
-        self assert:(stxGenerated = printfGenerated).
-        self assert:(printfGenerated = expected).
+	printfGenerated := val printfPrintString:fmt.
+	stxGenerated := PrintfScanf printf:fmt argument:val.
+	self assert:(stxGenerated = printfGenerated).
+	self assert:(printfGenerated = expected).
     ].
 !
 
@@ -2299,7 +2299,7 @@
     self assert:( '' unquote = '' ).
 
     self assert:( '""' unquote = '' ).
-    self assert:( c'\'\'' unquote = c'\'\'' ).
+    self assert:( '''''' unquote = c'''''' ).
 
     "/ ------------------------------------
 
@@ -2312,97 +2312,97 @@
 !
 
 test90_enumeratingLines
-    
+
     |  |
 
     #(
-        c''
-        c'abc'
-        c'\n'
-        c'abc\n'
-        c'\n\n'
-        c'abc\n\n'
-        c'\n\nabc'
-        c'\nabc\n'
-        c'abc\nabc\nabc'
-        c'abc\nabc\nabc\n'
-        c'abc\nabc\nabc\n\n'
-        c'a\nb\nc\n\n'
-        c'a\n\n\nb\nc\n\n\n\nd'
+	c''
+	c'abc'
+	c'\n'
+	c'abc\n'
+	c'\n\n'
+	c'abc\n\n'
+	c'\n\nabc'
+	c'\nabc\n'
+	c'abc\nabc\nabc'
+	c'abc\nabc\nabc\n'
+	c'abc\nabc\nabc\n\n'
+	c'a\nb\nc\n\n'
+	c'a\n\n\nb\nc\n\n\n\nd'
     ) do:[:eachTestString |
-        |testString sColl calledWith1 calledWith2 count1 count2 countReturned|
+	|testString sColl calledWith1 calledWith2 count1 count2 countReturned|
 
-        #( yourself asUnicode16String asUnicode32String ) do:[:conv |
-            testString := eachTestString perform:conv.
+	#( yourself asUnicode16String asUnicode32String ) do:[:conv |
+	    testString := eachTestString perform:conv.
 
-            "/ try asStringCollection as reference
-            sColl := testString asStringCollection.
-            count1 := 0.
-            calledWith1 := OrderedCollection new.
-            sColl do:[:each |
-                count1 := count1 + 1.
-                calledWith1 add:each.
-            ].
+	    "/ try asStringCollection as reference
+	    sColl := testString asStringCollection.
+	    count1 := 0.
+	    calledWith1 := OrderedCollection new.
+	    sColl do:[:each |
+		count1 := count1 + 1.
+		calledWith1 add:each.
+	    ].
 
-            "/ check asCollectionOfLinesDo: 
-            count2 := 0.
-            calledWith2 := OrderedCollection new.
-            countReturned := testString asCollectionOfLinesDo:[:each |
-                count2 := count2 + 1.
-                calledWith2 add:each.
-            ].
-            self assert:(count1 == count2).
-            self assert:(count2 == countReturned).
-            self assert:(calledWith1 = calledWith2).
-        ].
+	    "/ check asCollectionOfLinesDo:
+	    count2 := 0.
+	    calledWith2 := OrderedCollection new.
+	    countReturned := testString asCollectionOfLinesDo:[:each |
+		count2 := count2 + 1.
+		calledWith2 add:each.
+	    ].
+	    self assert:(count1 == count2).
+	    self assert:(count2 == countReturned).
+	    self assert:(calledWith1 = calledWith2).
+	].
     ].
 !
 
 test91_enumeratingWords
-    
+
     |  |
 
     #(
-        0 c''
-        1 c'abc'
-        0 c'\n'
-        1 c'abc\n'
-        0 c'\n\n'
-        1 c'abc\n\n'
-        1 c'\n\nabc'
-        1 c'\nabc\n'
-        3 c'abc\nabc\nabc'
-        3 c'abc\nabc\nabc\n'
-        3 c'abc\nabc\nabc\n\n'
-        3 c'a\nb\nc\n\n'
-        4 c'a\n\n\nb\nc\n\n\n\nd'
+	0 c''
+	1 c'abc'
+	0 c'\n'
+	1 c'abc\n'
+	0 c'\n\n'
+	1 c'abc\n\n'
+	1 c'\n\nabc'
+	1 c'\nabc\n'
+	3 c'abc\nabc\nabc'
+	3 c'abc\nabc\nabc\n'
+	3 c'abc\nabc\nabc\n\n'
+	3 c'a\nb\nc\n\n'
+	4 c'a\n\n\nb\nc\n\n\n\nd'
     ) pairWiseDo:[:expectedCount :eachTestString |
-        |testString sColl calledWith1 calledWith2 count1 count2 countReturned|
+	|testString sColl calledWith1 calledWith2 count1 count2 countReturned|
 
-        #( yourself asUnicode16String asUnicode32String ) do:[:conv |
-            testString := eachTestString perform:conv.
+	#( yourself asUnicode16String asUnicode32String ) do:[:conv |
+	    testString := eachTestString perform:conv.
 
-            "/ try asStringCollection as reference
-            sColl := testString asCollectionOfWords.
-            count1 := 0.
-            calledWith1 := OrderedCollection new.
-            sColl do:[:each |
-                count1 := count1 + 1.
-                calledWith1 add:each.
-            ].
+	    "/ try asStringCollection as reference
+	    sColl := testString asCollectionOfWords.
+	    count1 := 0.
+	    calledWith1 := OrderedCollection new.
+	    sColl do:[:each |
+		count1 := count1 + 1.
+		calledWith1 add:each.
+	    ].
 
-            "/ check asCollectionOfWordsDo: 
-            count2 := 0.
-            calledWith2 := OrderedCollection new.
-            countReturned := testString asCollectionOfWordsDo:[:each |
-                count2 := count2 + 1.
-                calledWith2 add:each.
-            ].
-            self assert:(count1 == expectedCount).
-            self assert:(count1 == count2).
-            self assert:(count2 == countReturned).
-            self assert:(calledWith1 = calledWith2).
-        ].
+	    "/ check asCollectionOfWordsDo:
+	    count2 := 0.
+	    calledWith2 := OrderedCollection new.
+	    countReturned := testString asCollectionOfWordsDo:[:each |
+		count2 := count2 + 1.
+		calledWith2 add:each.
+	    ].
+	    self assert:(count1 == expectedCount).
+	    self assert:(count1 == count2).
+	    self assert:(count2 == countReturned).
+	    self assert:(calledWith1 = calledWith2).
+	].
     ].
 ! !
 
@@ -2415,4 +2415,3 @@
 version_CVS
     ^ '$Header$'
 ! !
-