class: CharacterArray
authorClaus Gittinger <cg@exept.de>
Wed, 05 Mar 2014 00:01:45 +0100
changeset 16202 f83742e87419
parent 16201 0b2ca38fc441
child 16203 244aa42247b7
class: CharacterArray added: #copyReplaceAll:with: compatibility hack for ANSI
CharacterArray.st
--- a/CharacterArray.st	Tue Mar 04 16:05:28 2014 +0100
+++ b/CharacterArray.st	Wed Mar 05 00:01:45 2014 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
-	      All Rights Reserved
+              All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -12,11 +12,11 @@
 "{ Package: 'stx:libbasic' }"
 
 UninterpretedBytes variableByteSubclass:#CharacterArray
-	instanceVariableNames:''
-	classVariableNames:'PreviousMatch DecoderTables EncoderTables DecodingFailedSignal
-		EncodingFailedSignal'
-	poolDictionaries:''
-	category:'Collections-Text'
+        instanceVariableNames:''
+        classVariableNames:'PreviousMatch DecoderTables EncoderTables DecodingFailedSignal
+                EncodingFailedSignal'
+        poolDictionaries:''
+        category:'Collections-Text'
 !
 
 !CharacterArray class methodsFor:'documentation'!
@@ -24,7 +24,7 @@
 copyright
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
-	      All Rights Reserved
+              All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -44,11 +44,11 @@
     All this class does is provide common protocol for concrete subclasses.
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 
     [see also:]
-	String TwoByteString
-	StringCollection
+        String TwoByteString
+        StringCollection
 "
 ! !
 
@@ -56,11 +56,11 @@
 
 initialize
     DecodingFailedSignal isNil ifTrue:[
-	DecodingFailedSignal := DecodingError.
-	DecodingFailedSignal notifierString:'error during decode'.
-
-	EncodingFailedSignal :=EncodingError.
-	EncodingFailedSignal notifierString:'error during encode'.
+        DecodingFailedSignal := DecodingError.
+        DecodingFailedSignal notifierString:'error during decode'.
+
+        EncodingFailedSignal :=EncodingError.
+        EncodingFailedSignal notifierString:'error during encode'.
     ]
 
     "
@@ -88,13 +88,13 @@
     nBytes := aByteCollection size.
     mySize := self basicNew bitsPerCharacter.
     mySize == 16 ifTrue:[
-	newString := self basicNew:(nBytes // 2).
-	dstIdx := 1.
-	aByteCollection pairWiseDo:[:hi :lo |
-	    newString at:dstIdx put:(Character value:(hi bitShift:8)+lo).
-	    dstIdx := dstIdx + 1
-	].
-	^ newString.
+        newString := self basicNew:(nBytes // 2).
+        dstIdx := 1.
+        aByteCollection pairWiseDo:[:hi :lo |
+            newString at:dstIdx put:(Character value:(hi bitShift:8)+lo).
+            dstIdx := dstIdx + 1
+        ].
+        ^ newString.
     ].
 
     ^ (self basicNew:nBytes) replaceFrom:1 with:aByteCollection
@@ -134,12 +134,12 @@
     newString := ''.
     first := true.
     aCollectionOfStrings do:[:s |
-	first ifFalse:[
-	    newString := newString , aSeparatorString
-	] ifTrue:[
-	    first := false
-	].
-	newString := newString , s
+        first ifFalse:[
+            newString := newString , aSeparatorString
+        ] ifTrue:[
+            first := false
+        ].
+        newString := newString , s
     ].
     ^ newString
 
@@ -250,7 +250,7 @@
 
     new := self new: anArray size.
     1 to: anArray size do:[:index |
-	new at: index put: (anArray at: index) asCharacter
+        new at: index put: (anArray at: index) asCharacter
     ].
     ^new
 
@@ -639,61 +639,61 @@
     coll := OrderedCollection new.
     idx := 1. end := aString size.
     [idx <= end] whileTrue:[
-	|char this|
-
-	char := aString at:idx.
-	char == $* ifTrue:[
-	    previous ~~ #anyString ifTrue:[
-		this := #anyString
-	    ]
-	] ifFalse:[
-	    char == $# ifTrue:[
-		previous ~~ #anyString ifTrue:[
-		    this := #any
-		]
-	    ] ifFalse:[
-		char == $[ ifTrue:[
-		    matchSet := IdentitySet new.
-		    idx := idx + 1.
-		    idx > end ifTrue:[^ nil].
-		    char := aString at:idx.
-		    c1 := nil.
-		    [char ~~ $]] whileTrue:[
-			((char == $-) and:[c1 notNil]) ifTrue:[
-			    idx := idx + 1.
-			    idx > end ifTrue:[^ nil].
-			    c2 := aString at:idx.
-			    c1 to:c2 do:[:c | matchSet add:c].
-			    c1 := nil.
-			    idx := idx + 1.
-			] ifFalse:[
-			    (char ~~ $]) ifTrue:[
-				matchSet add:char.
-				c1 := char.
-				idx := idx + 1
-			    ]
-			].
-			idx > end ifTrue:[^ nil].
-			char := aString at:idx
-		    ].
-		    this := matchSet asString
-		] ifFalse:[
-		    char == escape ifTrue:[
-			idx := idx + 1.
-			idx > end ifTrue:[
-			    "/ mhmh - what should we do here ?
-			    this := char
-			] ifFalse:[
-			    this := aString at:idx.
-			]
-		    ] ifFalse:[
-			this := char
-		    ]
-		]
-	    ]
-	].
-	this notNil ifTrue:[coll add:this. previous := this].
-	idx := idx + 1
+        |char this|
+
+        char := aString at:idx.
+        char == $* ifTrue:[
+            previous ~~ #anyString ifTrue:[
+                this := #anyString
+            ]
+        ] ifFalse:[
+            char == $# ifTrue:[
+                previous ~~ #anyString ifTrue:[
+                    this := #any
+                ]
+            ] ifFalse:[
+                char == $[ ifTrue:[
+                    matchSet := IdentitySet new.
+                    idx := idx + 1.
+                    idx > end ifTrue:[^ nil].
+                    char := aString at:idx.
+                    c1 := nil.
+                    [char ~~ $]] whileTrue:[
+                        ((char == $-) and:[c1 notNil]) ifTrue:[
+                            idx := idx + 1.
+                            idx > end ifTrue:[^ nil].
+                            c2 := aString at:idx.
+                            c1 to:c2 do:[:c | matchSet add:c].
+                            c1 := nil.
+                            idx := idx + 1.
+                        ] ifFalse:[
+                            (char ~~ $]) ifTrue:[
+                                matchSet add:char.
+                                c1 := char.
+                                idx := idx + 1
+                            ]
+                        ].
+                        idx > end ifTrue:[^ nil].
+                        char := aString at:idx
+                    ].
+                    this := matchSet asString
+                ] ifFalse:[
+                    char == escape ifTrue:[
+                        idx := idx + 1.
+                        idx > end ifTrue:[
+                            "/ mhmh - what should we do here ?
+                            this := char
+                        ] ifFalse:[
+                            this := aString at:idx.
+                        ]
+                    ] ifFalse:[
+                        this := char
+                    ]
+                ]
+            ]
+        ].
+        this notNil ifTrue:[coll add:this. previous := this].
+        idx := idx + 1
     ].
 
     ^ coll asArray
@@ -725,7 +725,6 @@
     ^ self == CharacterArray
 ! !
 
-
 !CharacterArray methodsFor:'Compatibility-ANSI'!
 
 addLineDelimiters
@@ -753,18 +752,18 @@
 
     ds := WriteStream on:(self species new).
     self do:[:eachChar |
-	|repl|
-
-	repl := expandTable at:eachChar ifAbsent:nil.
-	repl isNil ifTrue:[
-	    ds nextPut:eachChar
-	] ifFalse:[
-	    repl size == 0 ifTrue:[
-		ds nextPut:repl
-	    ] ifFalse:[
-		ds nextPutAll:repl
-	    ]
-	].
+        |repl|
+
+        repl := expandTable at:eachChar ifAbsent:nil.
+        repl isNil ifTrue:[
+            ds nextPut:eachChar
+        ] ifFalse:[
+            repl size == 0 ifTrue:[
+                ds nextPut:repl
+            ] ifFalse:[
+                ds nextPutAll:repl
+            ]
+        ].
     ].
     ^ ds contents.
 !
@@ -891,7 +890,7 @@
      '12345678901234567890' replString:'234' withString:'foo'
 
      ('a string with spaces' replChar:$  withString:' foo ')
-	replString:'foo' withString:'bar'
+        replString:'foo' withString:'bar'
     "
 
     "Modified: / 12-05-2004 / 12:00:27 / cg"
@@ -1021,9 +1020,9 @@
     "cg: I am not sure, if this is really the squeak semantics (w.r.t. empty fields)"
 
     delimiterOrDelimiters size == 0 ifTrue:[
-	^ self asCollectionOfSubstringsSeparatedBy:delimiterOrDelimiters
+        ^ self asCollectionOfSubstringsSeparatedBy:delimiterOrDelimiters
     ] ifFalse:[
-	^ self asCollectionOfSubstringsSeparatedByAny:delimiterOrDelimiters
+        ^ self asCollectionOfSubstringsSeparatedByAny:delimiterOrDelimiters
     ].
 
     "
@@ -1062,7 +1061,7 @@
     "/ for now,  a q&d hack ...
 
     caseSensitive ifFalse:[
-	^ self asLowercase includesString:aString asLowercase
+        ^ self asLowercase includesString:aString asLowercase
     ].
     ^ self includesString:aString
 
@@ -1115,7 +1114,7 @@
      Assumes the delimiters to be a non-empty string."
 
     start to:self size do:[:i |
-	delimiters detect:[:delim | delim = (self at:i) ] ifNone:[ ^ i ]
+        delimiters detect:[:delim | delim = (self at:i) ] ifNone:[ ^ i ]
     ].
     ^ self size + 1
 
@@ -1244,24 +1243,6 @@
      '.......'     withoutTrailing:$.
      'foo'         withoutTrailing:$.
     "
-!
-
-withoutTrailingBlanks
-    "return a copy of myself without trailing spaces.
-     Notice: this does NOT remove tabs, newline or any other whitespace.
-     Returns an empty string, if the receiver consist only of spaces."
-
-    ^ self withoutTrailing:Character space
-
-    "
-     '    foo    ' withoutTrailingBlanks
-     'foo    '     withoutTrailingBlanks
-     '    foo'     withoutTrailingBlanks
-     '       '     withoutTrailingBlanks
-     'foo'         withoutTrailingBlanks
-     ('  ' , Character tab asString , ' foo   ') withoutTrailingBlanks inspect
-     ('   foo' , Character tab asString) withoutTrailingBlanks inspect
-    "
 ! !
 
 !CharacterArray methodsFor:'Compatibility-V''Age'!
@@ -1294,7 +1275,7 @@
 
     "
      'do you prefer %1 or rather %2 ?'
-	bindWith:'smalltalk' with:'c++'
+        bindWith:'smalltalk' with:'c++'
     "
 !
 
@@ -1307,7 +1288,7 @@
 
     "
      'do you prefer %1 or rather %2 (not talking about %3) ?'
-	bindWith:'smalltalk' with:'c++' with:'c'
+        bindWith:'smalltalk' with:'c++' with:'c'
     "
 !
 
@@ -1320,7 +1301,7 @@
 
     "
      'do you prefer %1 or rather %2 (not talking about %3 or even %4) ?'
-	bindWith:'smalltalk' with:'c++' with:'c' with:'assembler'
+        bindWith:'smalltalk' with:'c++' with:'c' with:'assembler'
     "
 !
 
@@ -1340,8 +1321,8 @@
      This has been added for VisualAge compatibility."
 
     ^ self expandPlaceholdersWith:(Array with:str1 with:str2
-					 with:str3 with:str4
-					 with:str5 with:str6)
+                                         with:str3 with:str4
+                                         with:str5 with:str6)
 !
 
 bindWith:str1 with:str2 with:str3 with:str4 with:str5 with:str6 with:str7
@@ -1350,9 +1331,9 @@
      This has been added for VisualAge compatibility."
 
     ^ self expandPlaceholdersWith:(Array with:str1 with:str2
-					 with:str3 with:str4
-					 with:str5 with:str6
-					 with:str7)
+                                         with:str3 with:str4
+                                         with:str5 with:str6
+                                         with:str7)
 !
 
 bindWith:str1 with:str2 with:str3 with:str4 with:str5 with:str6 with:str7 with:str8
@@ -1392,10 +1373,10 @@
 
     "
      'do you prefer %1 or rather %2 (not talking about %3) ?'
-	bindWithArguments:#('smalltalk' 'c++' 'c')
+        bindWithArguments:#('smalltalk' 'c++' 'c')
 
      'do you %(what) ?'
-	bindWithArguments:(Dictionary new at:#'what' put:'understand'; yourself)
+        bindWithArguments:(Dictionary new at:#'what' put:'understand'; yourself)
     "
 !
 
@@ -1533,94 +1514,94 @@
     out := CharacterWriteStream on:(self species uninitializedNew:self size).
 
     [in atEnd] whileFalse:[
-	c := in next.
-	c == $% ifTrue:[
-	    c := in next.
-	    out nextPut:c
-	] ifFalse:[c ~~ $< ifTrue:[
-	    out nextPut:c.
-	] ifFalse:[
-	    peekc := in peek.
-	    [peekc == $<] whileTrue:[
-		out nextPut:$<.
-		peekc := in nextPeek.
-	    ].
-	    peekc == $n ifTrue:[
-		peekc := in nextPeek.
-		peekc == $> ifTrue:[
-		    in next.
-		    out cr.
-		] ifFalse:[
-		    out nextPutAll:'<n'.
-		]
-	    ] ifFalse:[peekc == $t ifTrue:[
-		peekc := in nextPeek.
-		peekc == $> ifTrue:[
-		    in next.
-		    out tab.
-		] ifFalse:[
-		    out nextPutAll:'<t'.
-		]
-	    ] ifFalse:[
-		peekc isDigit ifTrue:[
-		    "start an argument expansion ..."
-		    nr := Integer readFrom:in onError:nil.
-		    nr isNil ifTrue:[
-			"this cannot happen (there is at least one digit)"
-			self error:'invalid format' mayProceed:true.
-			^ self
-		    ].
-		    fmt := in next.
-		    (fmt ~~ $? and:[in peek ~~ $>]) ifTrue:[
-			out nextPut:$<.
-			nr printOn:out.
-			out nextPut:fmt.
-		    ] ifFalse:[
-			(nr between:1 and:argArray size) ifTrue:[
-			    arg := argArray at:nr.
-			] ifFalse:[
-			    arg := ''
-			].
-
-			fmt == $p ifTrue:[
-			    "expand with args printString"
-			    arg printOn:out.
-			] ifFalse:[fmt == $s ifTrue:[
-			    "expand with arg itself"
-			    arg isText ifTrue:[
-				out contentsSpecies isText ifFalse:[
-				    out := (WriteStream on:Text new) nextPutAll:out contents; yourself.
-				].
-				out nextPutAll:arg.
-			    ] ifFalse:[
-				out nextPutAll:arg "asString" string.
-			    ]
-			] ifFalse:[fmt == $? ifTrue:[
-			    s1 := in upTo:$:.
-			    s2 := in nextUpTo:$>.
-			    arg == true ifTrue:[
-				out nextPutAll:s1
-			    ] ifFalse:[
-				out nextPutAll:s2
-			    ].
-			] ifFalse:[
-			    "what does VW do here ?"
-			    self error:'invalid format' mayProceed:true.
-			    ^ self
-			]]].
-			c := in next.
-			c ~~ $> ifTrue:[
-			    "what does VW do here ?"
-			    self error:'invalid format' mayProceed:true.
-			    ^ self
-			]
-
-		    ].
-		] ifFalse:[
-		    out nextPut:$<.
-		].
-	    ]].
-	]].
+        c := in next.
+        c == $% ifTrue:[
+            c := in next.
+            out nextPut:c
+        ] ifFalse:[c ~~ $< ifTrue:[
+            out nextPut:c.
+        ] ifFalse:[
+            peekc := in peek.
+            [peekc == $<] whileTrue:[
+                out nextPut:$<.
+                peekc := in nextPeek.
+            ].
+            peekc == $n ifTrue:[
+                peekc := in nextPeek.
+                peekc == $> ifTrue:[
+                    in next.
+                    out cr.
+                ] ifFalse:[
+                    out nextPutAll:'<n'.
+                ]
+            ] ifFalse:[peekc == $t ifTrue:[
+                peekc := in nextPeek.
+                peekc == $> ifTrue:[
+                    in next.
+                    out tab.
+                ] ifFalse:[
+                    out nextPutAll:'<t'.
+                ]
+            ] ifFalse:[
+                peekc isDigit ifTrue:[
+                    "start an argument expansion ..."
+                    nr := Integer readFrom:in onError:nil.
+                    nr isNil ifTrue:[
+                        "this cannot happen (there is at least one digit)"
+                        self error:'invalid format' mayProceed:true.
+                        ^ self
+                    ].
+                    fmt := in next.
+                    (fmt ~~ $? and:[in peek ~~ $>]) ifTrue:[
+                        out nextPut:$<.
+                        nr printOn:out.
+                        out nextPut:fmt.
+                    ] ifFalse:[
+                        (nr between:1 and:argArray size) ifTrue:[
+                            arg := argArray at:nr.
+                        ] ifFalse:[
+                            arg := ''
+                        ].
+
+                        fmt == $p ifTrue:[
+                            "expand with args printString"
+                            arg printOn:out.
+                        ] ifFalse:[fmt == $s ifTrue:[
+                            "expand with arg itself"
+                            arg isText ifTrue:[
+                                out contentsSpecies isText ifFalse:[
+                                    out := (WriteStream on:Text new) nextPutAll:out contents; yourself.
+                                ].
+                                out nextPutAll:arg.
+                            ] ifFalse:[
+                                out nextPutAll:arg "asString" string.
+                            ]
+                        ] ifFalse:[fmt == $? ifTrue:[
+                            s1 := in upTo:$:.
+                            s2 := in nextUpTo:$>.
+                            arg == true ifTrue:[
+                                out nextPutAll:s1
+                            ] ifFalse:[
+                                out nextPutAll:s2
+                            ].
+                        ] ifFalse:[
+                            "what does VW do here ?"
+                            self error:'invalid format' mayProceed:true.
+                            ^ self
+                        ]]].
+                        c := in next.
+                        c ~~ $> ifTrue:[
+                            "what does VW do here ?"
+                            self error:'invalid format' mayProceed:true.
+                            ^ self
+                        ]
+
+                    ].
+                ] ifFalse:[
+                    out nextPut:$<.
+                ].
+            ]].
+        ]].
     ].
     ^ out contents
 
@@ -1684,16 +1665,16 @@
     sz := self size.
     specialChars := '*#[\'.
     (escape := self class matchEscapeCharacter) ~~ $\ ifTrue:[
-	specialChars := specialChars copy.
-	specialChars at:specialChars size put:escape
+        specialChars := specialChars copy.
+        specialChars at:specialChars size put:escape
     ].
 
     [true] whileTrue:[
-	idx := self indexOfAny:specialChars startingAt:idx.
-	idx == 0 ifTrue:[^ false].
-	(self at:idx) == escape ifFalse:[^ true].
-	idx := idx + 2.
-	idx > sz ifTrue:[^ false].
+        idx := self indexOfAny:specialChars startingAt:idx.
+        idx == 0 ifTrue:[^ false].
+        (self at:idx) == escape ifFalse:[^ true].
+        idx := idx + 2.
+        idx > sz ifTrue:[^ false].
     ].
 
     "
@@ -1765,7 +1746,7 @@
     mySize := self size.
 
     start to:mySize do:[:index |
-	(self at:index) isSeparator ifFalse:[^ index]
+        (self at:index) isSeparator ifFalse:[^ index]
     ].
     ^ 0
 
@@ -1834,7 +1815,7 @@
     mySize := self size.
 
     start to:mySize do:[:index |
-	(self at:index) isSeparator ifTrue:[^ index]
+        (self at:index) isSeparator ifTrue:[^ index]
     ].
     ^ 0
 
@@ -1876,7 +1857,7 @@
     start := startIndex.
 
     start to:1 by:-1 do:[:index |
-	(self at:index) isSeparator ifTrue:[^ index]
+        (self at:index) isSeparator ifTrue:[^ index]
     ].
     ^ 0
 
@@ -1906,9 +1887,9 @@
     n := mySize min:otherSize.
 
     1 to:n do:[:index |
-	c1 := self at:index.
-	c2 := aString at:index.
-	(c1 == c2 or:[c1 = c2]) ifFalse:[^ c1 < c2].
+        c1 := self at:index.
+        c2 := aString at:index.
+        (c1 == c2 or:[c1 = c2]) ifFalse:[^ c1 < c2].
     ].
     ^ mySize < otherSize
 !
@@ -1962,9 +1943,9 @@
     n := mySize min:otherSize.
 
     1 to:n do:[:index |
-	c1 := self at:index.
-	c2 := aString at:index.
-	(c1 == c2 or:[c1 = c2]) ifFalse:[^ c1 > c2].
+        c1 := self at:index.
+        c2 := aString at:index.
+        (c1 == c2 or:[c1 = c2]) ifFalse:[^ c1 > c2].
     ].
     ^ mySize > otherSize
 
@@ -2038,10 +2019,10 @@
     n := mySize min:otherSize.
 
     1 to:n do:[:index |
-	c1 := (self at:index) asLowercase.
-	c2 := (aString at:index) asLowercase.
-	c1 > c2 ifTrue:[^ 1].
-	c1 < c2 ifTrue:[^ -1].
+        c1 := (self at:index) asLowercase.
+        c2 := (aString at:index) asLowercase.
+        c1 > c2 ifTrue:[^ 1].
+        c1 < c2 ifTrue:[^ -1].
     ].
     mySize > otherSize ifTrue:[^ 1].
     mySize < otherSize ifTrue:[^ -1].
@@ -2288,18 +2269,18 @@
      this value corrensponds to the number of replacements that have to be
      made to get aString from the receiver.
      The arguments are the costs for
-	s:substitution,
-	k:keyboard type (substitution),
-	c:case-change,
-	i:insertion
-	d:deletion
+        s:substitution,
+        k:keyboard type (substitution),
+        c:case-change,
+        i:insertion
+        d:deletion
      of a character.
      See IEEE transactions on Computers 1976 Pg 172 ff"
 
     ^ StringUtilities
-	    levenshteinDistanceFrom:self
-	    to:aString
-	    s:substWeight k:kbdTypoWeight c:caseWeight e:nil i:insrtWeight d:deleteWeight
+            levenshteinDistanceFrom:self
+            to:aString
+            s:substWeight k:kbdTypoWeight c:caseWeight e:nil i:insrtWeight d:deleteWeight
 !
 
 sameAs:aString
@@ -2316,11 +2297,11 @@
     mySize == otherSize ifFalse:[^ false].
 
     1 to:mySize do:[:index |
-	c1 := self at:index.
-	c2 := aString at:index.
-	c1 == c2 ifFalse:[
-	    (c1 sameAs:c2) ifFalse:[^ false].
-	]
+        c1 := self at:index.
+        c2 := aString at:index.
+        c1 == c2 ifFalse:[
+            (c1 sameAs:c2) ifFalse:[^ false].
+        ]
     ].
     ^ true
 
@@ -2356,7 +2337,7 @@
      if false, this is the same as #=."
 
     ignoreCase ifTrue:[
-	^ self sameAs:aString
+        ^ self sameAs:aString
     ].
     ^ self = aString
 
@@ -2379,12 +2360,12 @@
 
     cnt := 0.
     1 to:n do:[:index |
-	c1 := self at:index.
-	c2 := aString at:index.
-	((c1 == c2)
-	or:[c1 asLowercase = c2 asLowercase]) ifTrue:[
-	    cnt := cnt + 1
-	]
+        c1 := self at:index.
+        c2 := aString at:index.
+        ((c1 == c2)
+        or:[c1 asLowercase = c2 asLowercase]) ifTrue:[
+            cnt := cnt + 1
+        ]
     ].
     ^ cnt
 
@@ -2470,24 +2451,24 @@
     score := 0.
     i1 := i2 := 1.
     [i1 <= size1 and: [i2 <= size2]] whileTrue:[
-	next1 := i1 + 1.
-	next2 := i2 + 1.
-	(self at:i1) == (aString at:i2) ifTrue: [
-	    score := score+1.
-	    i1 := next1.
-	    i2 := next2
-	] ifFalse: [
-	    (i2 < size2 and: [(self at:i1) == (aString at:next2)]) ifTrue: [
-		i2 := next2
-	    ] ifFalse: [
-		(i1 < size1 and: [(self at:next1) == (aString at:i2)]) ifTrue: [
-		    i1 := next1
-		] ifFalse: [
-		    i1 := next1.
-		    i2 := next2
-		]
-	    ]
-	]
+        next1 := i1 + 1.
+        next2 := i2 + 1.
+        (self at:i1) == (aString at:i2) ifTrue: [
+            score := score+1.
+            i1 := next1.
+            i2 := next2
+        ] ifFalse: [
+            (i2 < size2 and: [(self at:i1) == (aString at:next2)]) ifTrue: [
+                i2 := next2
+            ] ifFalse: [
+                (i1 < size1 and: [(self at:next1) == (aString at:i2)]) ifTrue: [
+                    i1 := next1
+                ] ifFalse: [
+                    i1 := next1.
+                    i2 := next2
+                ]
+            ]
+        ]
     ].
 
     score == maxLen ifTrue: [^ 100].
@@ -2509,7 +2490,7 @@
     |s|
 
     (s := self string) ~~ self ifTrue:[
-	^ s startsWith:aString
+        ^ s startsWith:aString
     ].
     ^ super startsWith:aString
 
@@ -2537,7 +2518,7 @@
      '1 one two three four 5 five' asArrayOfSubstrings
      '1
 one
-	two three four 5 five' asArrayOfSubstrings
+        two three four 5 five' asArrayOfSubstrings
     "
 !
 
@@ -2832,18 +2813,18 @@
     start := 1.
     mySize := self size.
     [start <= mySize] whileTrue:[
-	start := self indexOfNonSeparatorStartingAt:start.
-	start == 0 ifTrue:[
-	    ^ count
-	].
-	stop := self indexOfSeparatorStartingAt:start.
-	stop == 0 ifTrue:[
-	    aBlock value:(self copyFrom:start to:mySize).
-	    ^ count + 1
-	].
-	aBlock value:(self copyFrom:start to:(stop - 1)).
-	start := stop.
-	count := count + 1
+        start := self indexOfNonSeparatorStartingAt:start.
+        start == 0 ifTrue:[
+            ^ count
+        ].
+        stop := self indexOfSeparatorStartingAt:start.
+        stop == 0 ifTrue:[
+            aBlock value:(self copyFrom:start to:mySize).
+            ^ count + 1
+        ].
+        aBlock value:(self copyFrom:start to:(stop - 1)).
+        start := stop.
+        count := count + 1
     ].
     ^ count
 
@@ -2932,10 +2913,10 @@
      '-1234' asInteger
 
      The following raises an error:
-	 '0.123' asInteger              <- reader finds more after reading 0
+         '0.123' asInteger              <- reader finds more after reading 0
 
      whereas the less strict readFrom does not:
-	 Integer readFrom:'0.123'       <- reader stops at ., returning 0
+         Integer readFrom:'0.123'       <- reader stops at ., returning 0
 
      '0.123' asInteger
      '0.123' asNumber    <- returns what you expect
@@ -2982,9 +2963,9 @@
     firstChar == firstCharAsLowercase ifTrue:[ ^ self].
 
     firstCharAsLowercase bitsPerCharacter > self bitsPerCharacter ifTrue:[
-	newString := firstCharAsLowercase stringSpecies fromString:self.
+        newString := firstCharAsLowercase stringSpecies fromString:self.
     ] ifFalse:[
-	newString := self stringSpecies fromString:self.
+        newString := self stringSpecies fromString:self.
     ].
     newString at:1 put:firstCharAsLowercase.
     ^ newString
@@ -3004,7 +2985,7 @@
     sz := self size.
     newString := self copyFrom:1 to:sz.
     sz > 0 ifTrue:[
-	newString at:sz put:(newString at:sz) asLowercase
+        newString at:sz put:(newString at:sz) asLowercase
     ].
     ^ newString
 
@@ -3095,14 +3076,14 @@
 
     newString := String new:(self size).
     1 to:self size do:[:idx |
-	|char|
-
-	char := self at:idx.
-	char codePoint <= 16rFF ifTrue:[
-	    newString at:idx put:char
-	] ifFalse:[
-	    newString at:idx put:replacementCharacter
-	].
+        |char|
+
+        char := self at:idx.
+        char codePoint <= 16rFF ifTrue:[
+            newString at:idx put:char
+        ] ifFalse:[
+            newString at:idx put:replacementCharacter
+        ].
     ].
     ^ newString
 
@@ -3138,7 +3119,7 @@
 asSymbolIfInterned
     "If a symbol with the receivers characters is already known, return it. Otherwise, return nil.
      This can be used to query for an existing symbol and is the same as:
-	self knownAsSymbol ifTrue:[self asSymbol] ifFalse:[nil]
+        self knownAsSymbol ifTrue:[self asSymbol] ifFalse:[nil]
      but slightly faster, since the symbol lookup operation is only performed once.
      The receiver must be a singleByte-String.
      TwoByte- and FourByteSymbols are (currently ?) not allowed."
@@ -3178,15 +3159,15 @@
     bitsPerCharacter := newStr bitsPerCharacter.
 
     1 to:mySize do:[:i |
-	i == 1 ifTrue:[
-	    c := (self at:i) asTitlecase.
-	] ifFalse:[
-	    c := (self at:i) asLowercase.
-	].
-	c bitsPerCharacter > bitsPerCharacter ifTrue:[
-	    newStr := c stringSpecies fromString:newStr.
-	].
-	newStr at:i put:c
+        i == 1 ifTrue:[
+            c := (self at:i) asTitlecase.
+        ] ifFalse:[
+            c := (self at:i) asLowercase.
+        ].
+        c bitsPerCharacter > bitsPerCharacter ifTrue:[
+            newStr := c stringSpecies fromString:newStr.
+        ].
+        newStr at:i put:c
     ].
     ^ newStr
 
@@ -3225,9 +3206,9 @@
     firstChar == firstCharAsTitlecase ifTrue:[ ^ self].
 
     firstCharAsTitlecase bitsPerCharacter > self bitsPerCharacter ifTrue:[
-	newString := firstCharAsTitlecase stringSpecies fromString:self.
+        newString := firstCharAsTitlecase stringSpecies fromString:self.
     ] ifFalse:[
-	newString := self stringSpecies fromString:self.
+        newString := self stringSpecies fromString:self.
     ].
     newString at:1 put:firstCharAsTitlecase.
     ^ newString
@@ -3314,11 +3295,11 @@
     bitsPerCharacter := newStr bitsPerCharacter.
 
     1 to:mySize do:[:i |
-	c := (self at:i) asUppercase.
-	c bitsPerCharacter > bitsPerCharacter ifTrue:[
-	    newStr := c stringSpecies fromString:newStr.
-	].
-	newStr at:i put:c
+        c := (self at:i) asUppercase.
+        c bitsPerCharacter > bitsPerCharacter ifTrue:[
+            newStr := c stringSpecies fromString:newStr.
+        ].
+        newStr at:i put:c
     ].
     ^ newStr
 
@@ -3343,9 +3324,9 @@
 
     "/ very seldom, the uppercase-char needs more bits than the lowercase one (turkish y-diaresis)
     firstCharAsUppercase bitsPerCharacter > self bitsPerCharacter ifTrue:[
-	newString := firstCharAsUppercase stringSpecies fromString:self.
+        newString := firstCharAsUppercase stringSpecies fromString:self.
     ] ifFalse:[
-	newString := self stringSpecies fromString:self.
+        newString := self stringSpecies fromString:self.
     ].
     newString at:1 put:firstCharAsUppercase.
     ^ newString
@@ -3366,7 +3347,7 @@
     sz := self size.
     newString := self copyFrom:1 to:sz.
     sz > 0 ifTrue:[
-	newString at:sz put:(newString at:sz) asUppercase
+        newString at:sz put:(newString at:sz) asUppercase
     ].
     ^ newString
 
@@ -3403,18 +3384,18 @@
     |myWidth otherWidth|
 
     aStringOrCharacter isCharacter ifTrue:[
-	^ self copyWith:aStringOrCharacter
+        ^ self copyWith:aStringOrCharacter
     ].
     aStringOrCharacter isText ifTrue:[
-	^ aStringOrCharacter concatenateFromString:self
+        ^ aStringOrCharacter concatenateFromString:self
     ].
     aStringOrCharacter isString ifTrue:[
-	(otherWidth := aStringOrCharacter bitsPerCharacter) ~~ (myWidth := self bitsPerCharacter) ifTrue:[
-	    otherWidth > myWidth ifTrue:[
-		^ (aStringOrCharacter species fromString:self) , aStringOrCharacter
-	    ].
-	    ^ self , (self species fromString:aStringOrCharacter)
-	].
+        (otherWidth := aStringOrCharacter bitsPerCharacter) ~~ (myWidth := self bitsPerCharacter) ifTrue:[
+            otherWidth > myWidth ifTrue:[
+                ^ (aStringOrCharacter species fromString:self) , aStringOrCharacter
+            ].
+            ^ self , (self species fromString:aStringOrCharacter)
+        ].
     ].
     ^ super , aStringOrCharacter
 
@@ -3426,7 +3407,7 @@
      (JISEncodedString fromString:'hello') , ' world'
 
      Transcript showCR:
-	 (Text string:'hello' emphasis:#italic) , (Text string:' world' emphasis:#bold)
+         (Text string:'hello' emphasis:#italic) , (Text string:' world' emphasis:#bold)
     "
 
     "Modified: 28.6.1997 / 00:13:17 / cg"
@@ -3455,7 +3436,7 @@
 
     n1 := n2 := maxLen // 2.
     maxLen odd ifTrue:[
-	n2 := n1 + 1
+        n2 := n1 + 1
     ].
     ^ (self copyFrom:1 to:n1) , (self copyFrom:sz - n2 + 1)
 
@@ -3597,6 +3578,26 @@
     "Modified (comment): / 24-11-2011 / 19:17:46 / cg"
 !
 
+copyReplaceAll:oldElement with:newElement
+    "return a copy of the receiver as a string, where all elements equal to oldElement
+     have been replaced by newElement."
+
+    "/ ANSI seems to allow a sequence to be replaced by another sequence,
+    "/ whereas the old ST80 meant replace all occurrences... - sigh.
+    oldElement isByteCollection ifTrue:[
+        newElement isByteCollection ifTrue:[
+            ^ self copyReplaceString:oldElement withString:newElement.
+        ].
+        self halt:'check if this is legal'.
+    ].
+    newElement isByteCollection ifTrue:[
+        self halt:'check if this is legal'.
+    ].
+    ^ self asString replaceAll:oldElement with:newElement
+
+    "Created: / 18.7.1998 / 23:03:38 / cg"
+!
+
 copyReplaceString:subString withString:newString
     "return a copy of the receiver, with all sequences of subString replaced
      by newString (i.e. slice in the newString in place of the oldString)."
@@ -3641,11 +3642,11 @@
     |sz newString|
 
     aCharacter bitsPerCharacter > self bitsPerCharacter ifTrue:[
-	sz := self size.
-	newString := aCharacter stringSpecies new:sz + 1.
-	newString replaceFrom:1 to:sz with:self startingAt:1.
-	newString at:sz+1 put:aCharacter.
-	^ newString.
+        sz := self size.
+        newString := aCharacter stringSpecies new:sz + 1.
+        newString replaceFrom:1 to:sz with:self startingAt:1.
+        newString at:sz+1 put:aCharacter.
+        ^ newString.
     ].
     ^ super copyWith:aCharacter
 ! !
@@ -3666,9 +3667,9 @@
     "q&d hack"
 
     (start == 1 and:[stop == self size]) ifTrue:[
-	self displayOn:aGC x:x y:y opaque:opaque.
+        self displayOn:aGC x:x y:y opaque:opaque.
     ] ifFalse:[
-	(self copyFrom:start to:stop) displayOn:aGC x:x y:y opaque:opaque.
+        (self copyFrom:start to:stop) displayOn:aGC x:x y:y opaque:opaque.
     ].
 !
 
@@ -3680,9 +3681,9 @@
 
     s := self string.
     opaque ifTrue:[
-	aGc displayOpaqueString:s x:x y:y.
+        aGc displayOpaqueString:s x:x y:y.
     ] ifFalse:[
-	aGc displayString:s x:x y:y.
+        aGc displayString:s x:x y:y.
     ].
 
     "Modified: 11.5.1996 / 14:42:48 / cg"
@@ -3975,9 +3976,9 @@
       is self-inverse, so the same code can be used for encoding and decoding."
 
     ^ self species
-	streamContents:[:aStream |
-	    self do:[:char |
-		aStream nextPut:(char rot:n) ]]
+        streamContents:[:aStream |
+            self do:[:char |
+                aStream nextPut:(char rot:n) ]]
 
     "
      'hello world' rot:13
@@ -4052,17 +4053,17 @@
     out := WriteStream on:(String uninitializedNew:self size).
     in := self readStream.
     [in atEnd] whileFalse:[
-	c := Character utf8DecodeFrom:in.
-	c codePoint > 16rFF ifTrue:[
-	    c := replacementCharacter
-	].
-	out nextPut:c.
+        c := Character utf8DecodeFrom:in.
+        c codePoint > 16rFF ifTrue:[
+            c := replacementCharacter
+        ].
+        out nextPut:c.
     ].
     ^ out contents
 
     "
      (Character value:16r220) utf8Encoded
-	utf8DecodedWithTwoByteCharactersReplacedBy:(Character space)
+        utf8DecodedWithTwoByteCharactersReplacedBy:(Character space)
     "
 !
 
@@ -4225,7 +4226,7 @@
      if not found, return 0.
 
      NOTICE: match-meta character interpretation is like in unix-matching,
-	     NOT the ST-80 meaning.
+             NOT the ST-80 meaning.
      NOTICE: this GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the argument is the match pattern"
 
@@ -4238,7 +4239,7 @@
      if not found, return 0.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
-	     NOT the ST-80 meaning.
+             NOT the ST-80 meaning.
      NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the argument is the match pattern"
 
@@ -4347,7 +4348,7 @@
      find matchstring; if found, return true, otherwise return false.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
-	     NOT the ST-80 meaning.
+             NOT the ST-80 meaning.
      NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the argument is the match pattern"
 
@@ -4366,7 +4367,7 @@
      find matchstring; if found, return true, otherwise return false.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
-	     NOT the ST-80 meaning.
+             NOT the ST-80 meaning.
      NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the argument is the match pattern"
 
@@ -4510,7 +4511,7 @@
      Lower/uppercase are considered different.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
-	     NOT the ST-80 meaning.
+             NOT the ST-80 meaning.
      NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the receiver is the match pattern"
 
@@ -4604,13 +4605,13 @@
      The escape character is the backQuote.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
-	     NOT the ST-80 meaning.
+             NOT the ST-80 meaning.
      NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the receiver is the match pattern"
 
     ^ self
-	match:aString from:start to:stop ignoreCase:ignoreCase
-	escapeCharacter:(self class matchEscapeCharacter)
+        match:aString from:start to:stop ignoreCase:ignoreCase
+        escapeCharacter:(self class matchEscapeCharacter)
 
     "
      '*ute*' match:'12345COMPUTER' from:1 to:5 ignoreCase:true
@@ -4697,7 +4698,7 @@
      If ignoreCase is true, lower/uppercase are considered the same.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
-	     NOT the ST-80 meaning.
+             NOT the ST-80 meaning.
      NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the receiver is the match pattern"
 
@@ -4716,14 +4717,14 @@
      '*some*compl*ern*' match:'this is another complicated pattern match' ignoreCase:true
 
      Time millisecondsToRun:[
-	Symbol allInstancesDo:[:sym |
-	    '[ab]*' match:sym ignoreCase:false
-	]
+        Symbol allInstancesDo:[:sym |
+            '[ab]*' match:sym ignoreCase:false
+        ]
      ].
      Time millisecondsToRun:[
-	Symbol allInstancesDo:[:sym |
-	    '*at:*' match:sym ignoreCase:false
-	]
+        Symbol allInstancesDo:[:sym |
+            '*at:*' match:sym ignoreCase:false
+        ]
      ].
     "
 
@@ -4737,7 +4738,7 @@
      Lower/uppercase are considered different.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
-	     NOT the ST-80 meaning.
+             NOT the ST-80 meaning.
      NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the receiver is the match pattern"
 
@@ -4806,9 +4807,9 @@
 
     len := self size.
     (len < size) ifTrue:[
-	s := self species new:size withAll:padCharacter.
-	s replaceFrom:(size - len) // 2  + 1 with:self.
-	^ s
+        s := self species new:size withAll:padCharacter.
+        s replaceFrom:(size - len) // 2  + 1 with:self.
+        ^ s
     ]
 
     "
@@ -4832,11 +4833,11 @@
      (sounds complicated ? -> see examples below)."
 
     ^ self
-	decimalPaddedTo:size
-	and:afterPeriod
-	at:decimalCharacter
-	withLeft:(Character space)
-	right:$0
+        decimalPaddedTo:size
+        and:afterPeriod
+        at:decimalCharacter
+        withLeft:(Character space)
+        right:$0
 
     "
      '123' decimalPaddedTo:10 and:3 at:$.      -> '   123    '
@@ -4865,25 +4866,25 @@
 
     idx := self indexOf:decimalCharacter.
     idx == 0 ifTrue:[
-	"/
-	"/ no decimal point found; adjust string to the left of the period column
-	"/
-	rightPadChar isNil ifTrue:[
-	    s := self , (self species new:afterPeriod + 1 withAll:leftPadChar)
-	] ifFalse:[
-	    s:= self , decimalCharacter asString , (self species new:afterPeriod withAll:rightPadChar).
-	].
+        "/
+        "/ no decimal point found; adjust string to the left of the period column
+        "/
+        rightPadChar isNil ifTrue:[
+            s := self , (self species new:afterPeriod + 1 withAll:leftPadChar)
+        ] ifFalse:[
+            s:= self , decimalCharacter asString , (self species new:afterPeriod withAll:rightPadChar).
+        ].
     ] ifFalse:[
 
-	"/ the number of after-decimalPoint characters
-	n := self size - idx.
-	rest := afterPeriod - n.
-	rest > 0 ifTrue:[
-	    s := (self species new:rest withAll:(rightPadChar ? leftPadChar)).
-	] ifFalse:[
-	    s := ''
-	].
-	s := self , s.
+        "/ the number of after-decimalPoint characters
+        n := self size - idx.
+        rest := afterPeriod - n.
+        rest > 0 ifTrue:[
+            s := (self species new:rest withAll:(rightPadChar ? leftPadChar)).
+        ] ifFalse:[
+            s := ''
+        ].
+        s := self , s.
     ].
 
     ^ s leftPaddedTo:size with:leftPadChar
@@ -4940,15 +4941,15 @@
 
     firstChar := (self at:1) asLowercase.
     ((firstChar isVowel and:[firstChar ~~ $u]) or:[firstChar == $x]) ifTrue:[
-	^ 'an'
+        ^ 'an'
     ].
     ^ 'a'
 
     "
-	'uboot' article.
-	'xmas' article.
-	'alarm' article.
-	'baby' article.
+        'uboot' article.
+        'xmas' article.
+        'alarm' article.
+        'baby' article.
     "
 !
 
@@ -4995,8 +4996,8 @@
     "/ what a kludge - Dolphin and Squeak mean: printOn: a stream;
     "/ ST/X (and some old ST80's) mean: draw-yourself on a GC.
     (aGCOrStream isStream or:[aGCOrStream == Transcript]) ifTrue:[
-	self storeOn:aGCOrStream.
-	^ self
+        self storeOn:aGCOrStream.
+        ^ self
     ].
     ^ super displayOn:aGCOrStream
 !
@@ -5017,8 +5018,8 @@
     "put the raw storeString of myself on aStream"
 
     self do:[:thisChar |
-	(thisChar == $') ifTrue:[aStream nextPut:thisChar].
-	aStream nextPut:thisChar
+        (thisChar == $') ifTrue:[aStream nextPut:thisChar].
+        aStream nextPut:thisChar
     ]
 
     "Modified: / 15.6.1998 / 17:21:17 / cg"
@@ -5143,8 +5144,8 @@
     idx := startIndex.
 
     1 to:sz do:[:i |
-	(self at:idx) ~~ (aString at:i) ifTrue:[^ false].
-	idx := idx + 1
+        (self at:idx) ~~ (aString at:i) ifTrue:[^ false].
+        idx := idx + 1
     ].
     ^ true
 
@@ -5169,17 +5170,17 @@
     start := 1.
     mySize := self size.
     [start <= mySize] whileTrue:[
-	ch := self at:start.
-	ch isSeparator ifTrue:[
-	    start := start + 1
-	] ifFalse:[
-	    stop := self indexOfSeparatorStartingAt:start.
-	    (stop == 0) ifTrue:[
-		stop := mySize + 1
-	    ].
-	    tally := tally + 1.
-	    start := stop
-	]
+        ch := self at:start.
+        ch isSeparator ifTrue:[
+            start := start + 1
+        ] ifFalse:[
+            stop := self indexOfSeparatorStartingAt:start.
+            (stop == 0) ifTrue:[
+                stop := mySize + 1
+            ].
+            tally := tally + 1.
+            start := stop
+        ]
     ].
     ^ tally
 
@@ -5285,8 +5286,8 @@
     coll := OrderedCollection new.
     s := ReadStream on:self.
     [s atEnd] whileFalse:[
-	part := s through:$:.
-	coll add:part
+        part := s through:$:.
+        coll add:part
     ].
     ^ coll asArray
 
@@ -5318,8 +5319,8 @@
     index := 1.
     end := self size.
     [index <= end] whileTrue:[
-	(self at:index) isSeparator ifFalse:[^ index - 1].
-	index := index + 1
+        (self at:index) isSeparator ifFalse:[^ index - 1].
+        index := index + 1
     ].
     ^ end
 
@@ -5705,7 +5706,7 @@
 
 tokensBasedOn:aCharacter
     "this is an ST-80 alias for the ST/X method
-	asCollectionOfSubstringsSeparatedBy:"
+        asCollectionOfSubstringsSeparatedBy:"
 
     ^ self asCollectionOfSubstringsSeparatedBy:aCharacter
 
@@ -5817,11 +5818,11 @@
     in := self readStream.
     out := WriteStream on:(self species new:self size).
     [in atEnd] whileFalse:[
-	c := in next.
-	(c == escape or:['*[#' includes:c]) ifTrue:[
-	    out nextPut:$\.
-	].
-	out nextPut:c.
+        c := in next.
+        (c == escape or:['*[#' includes:c]) ifTrue:[
+            out nextPut:$\.
+        ].
+        out nextPut:c.
     ].
     ^ out contents.
 
@@ -5924,19 +5925,19 @@
      ('123456789' , Character tab asString , 'x') withTabsExpanded
 
      (String with:Character tab
-	     with:Character tab
-	     with:$1) withTabsExpanded
+             with:Character tab
+             with:$1) withTabsExpanded
 
      (String with:Character tab
-	     with:$1
-	     with:Character tab
-	     with:$2) withTabsExpanded
+             with:$1
+             with:Character tab
+             with:$2) withTabsExpanded
 
      (String with:Character tab
-	     with:$1
-	     with:Character cr
-	     with:Character tab
-	     with:$2) withTabsExpanded
+             with:$1
+             with:Character cr
+             with:Character tab
+             with:$2) withTabsExpanded
     "
 
     "Modified: 12.5.1996 / 13:05:10 / cg"
@@ -5965,19 +5966,19 @@
 
     col := 1. newSz := 0.
     1 to:sz do:[:srcIdx |
-	ch := self at:srcIdx.
-	ch == Character tab ifFalse:[
-	    col := col + 1.
-	    newSz := newSz + 1.
-	    ch == Character cr ifTrue:[
-		col := 1
-	    ].
-	] ifTrue:[
-	    (col \\ numSpaces) to:numSpaces do:[:ii |
-		newSz := newSz + 1.
-		col := col + 1
-	    ].
-	]
+        ch := self at:srcIdx.
+        ch == Character tab ifFalse:[
+            col := col + 1.
+            newSz := newSz + 1.
+            ch == Character cr ifTrue:[
+                col := 1
+            ].
+        ] ifTrue:[
+            (col \\ numSpaces) to:numSpaces do:[:ii |
+                newSz := newSz + 1.
+                col := col + 1
+            ].
+        ]
     ].
 
     str := self species new:newSz.
@@ -5986,26 +5987,26 @@
 
     col := 1. dstIdx := 1.
     1 to:sz do:[:srcIdx |
-	ch := self at:srcIdx.
-
-	ch == Character tab ifFalse:[
-	    col := col + 1.
-	    ch == Character cr ifTrue:[
-		col := 1
-	    ].
-	    hasEmphasis ifTrue:[
-		e := self emphasisAt:srcIdx.
-		str emphasisAt:dstIdx put:e
-	    ].
-	    str at:dstIdx put:ch.
-	    dstIdx := dstIdx + 1
-	] ifTrue:[
-	    (col \\ numSpaces) to:numSpaces do:[:ii |
-		str at:dstIdx put:Character space.
-		dstIdx := dstIdx + 1.
-		col := col + 1
-	    ].
-	]
+        ch := self at:srcIdx.
+
+        ch == Character tab ifFalse:[
+            col := col + 1.
+            ch == Character cr ifTrue:[
+                col := 1
+            ].
+            hasEmphasis ifTrue:[
+                e := self emphasisAt:srcIdx.
+                str emphasisAt:dstIdx put:e
+            ].
+            str at:dstIdx put:ch.
+            dstIdx := dstIdx + 1
+        ] ifTrue:[
+            (col \\ numSpaces) to:numSpaces do:[:ii |
+                str at:dstIdx put:Character space.
+                dstIdx := dstIdx + 1.
+                col := col + 1
+            ].
+        ]
     ].
     ^ str
 
@@ -6019,19 +6020,19 @@
      ('123456789' , Character tab asString , 'x') withTabsExpanded
 
      (String with:Character tab
-	     with:Character tab
-	     with:$1) withTabsExpanded
+             with:Character tab
+             with:$1) withTabsExpanded
 
      (String with:Character tab
-	     with:$1
-	     with:Character tab
-	     with:$2) withTabsExpanded
+             with:$1
+             with:Character tab
+             with:$2) withTabsExpanded
 
      (String with:Character tab
-	     with:$1
-	     with:Character cr
-	     with:Character tab
-	     with:$2) withTabsExpanded
+             with:$1
+             with:Character cr
+             with:Character tab
+             with:$2) withTabsExpanded
     "
 
     "Modified: 12.5.1996 / 13:05:10 / cg"
@@ -6208,10 +6209,10 @@
 
     index := self indexOfNonSeparatorStartingAt:1.
     index ~~ 0 ifTrue:[
-	index == 1 ifTrue:[
-	    ^ self
-	].
-	^ self copyFrom:index
+        index == 1 ifTrue:[
+            ^ self
+        ].
+        ^ self copyFrom:index
     ].
     ^ ''
 
@@ -6236,13 +6237,13 @@
     in := self readStream.
     out := self species writeStream.
     [in atEnd] whileFalse:[
-	c := in next.
-	c == escape ifTrue:[
-	    in atEnd ifFalse:[
-		c := in next.
-	    ]
-	].
-	out nextPut:c.
+        c := in next.
+        c == escape ifTrue:[
+            in atEnd ifFalse:[
+                c := in next.
+            ]
+        ].
+        out nextPut:c.
     ].
     ^ out contents.
 
@@ -6265,7 +6266,7 @@
      Otherwise return the receiver"
 
     (self startsWith:aString) ifTrue:[
-	^ self copyFrom:aString size + 1
+        ^ self copyFrom:aString size + 1
     ].
     ^ self
 
@@ -6555,7 +6556,7 @@
      if it matches return the right.
      Finally, if strip is true, remove whiteSpace.
      This method is used to match and extract lines of the form:
-	something: rest
+        something: rest
      where we are interested in rest, but only if the receiver string
      begins with something.
 
@@ -6568,11 +6569,11 @@
     |rest|
 
     (self startsWith:keyword) ifTrue:[
-	rest := self copyFrom:(keyword size + 1).
-	strip ifTrue:[
-	    rest := rest withoutSeparators
-	].
-	^ rest
+        rest := self copyFrom:(keyword size + 1).
+        strip ifTrue:[
+            rest := rest withoutSeparators
+        ].
+        ^ rest
     ].
     ^ nil
 
@@ -6626,7 +6627,7 @@
     |string|
 
     (string := self string) ~~ self ifTrue:[
-	^ string contains8BitCharacters
+        ^ string contains8BitCharacters
     ].
     ^ self contains:[:aCharacter | aCharacter codePoint > 16r7F ].
 
@@ -6641,8 +6642,8 @@
      i.e. consists of a letter followed by letters or digits."
 
     self size == 0 ifTrue:[
-	"mhmh what is this ?"
-	^ false
+        "mhmh what is this ?"
+        ^ false
     ].
     (self at:1) isLetter ifFalse:[^ false].
     ^ self conform:[:char | char isLetterOrDigit].
@@ -6707,16 +6708,16 @@
 
     state := #initial.
     self do:[:char |
-	(state == #initial or:[ state == #gotColon]) ifTrue:[
-	    (char isLetter or:[ char == $_ ]) ifFalse:[^ false].
-	    state := #gotCharacter.
-	] ifFalse:[
-	    char == $: ifTrue:[
-		state := #gotColon.
-	    ] ifFalse:[
-		(char isLetterOrDigit or:[char == $_]) ifFalse:[^ false].
-	    ].
-	].
+        (state == #initial or:[ state == #gotColon]) ifTrue:[
+            (char isLetter or:[ char == $_ ]) ifFalse:[^ false].
+            state := #gotCharacter.
+        ] ifFalse:[
+            char == $: ifTrue:[
+                state := #gotColon.
+            ] ifFalse:[
+                (char isLetterOrDigit or:[char == $_]) ifFalse:[^ false].
+            ].
+        ].
     ].
     ^ state == #gotColon.
 
@@ -6771,7 +6772,7 @@
      i.e. consists only of digits."
 
     self size == 0 ifTrue:[
-	^ false
+        ^ false
     ].
     ^ self conform:[:char | char isDigit]
 
@@ -6822,12 +6823,12 @@
     scanner := Compiler new.
     scanner source:(self readStream).
     Parser parseErrorSignal handle:[:ex |
-	tok := nil.
+        tok := nil.
     ] do:[
-	tok := scanner nextToken.
+        tok := scanner nextToken.
     ].
     tok ~~ #Identifier ifTrue:[
-	^ false
+        ^ false
     ].
     scanner tokenPosition == 1 ifFalse:[^ false].
     ^ scanner sourceStream atEnd.
@@ -6857,10 +6858,10 @@
     |binopChars|
 
     (self size <= Scanner maxBinarySelectorSize) ifTrue:[
-	binopChars := Scanner binarySelectorCharacters.
-	(self conform:[:eachChar | (binopChars includes:eachChar)]) ifTrue:[
-	    ^ 1
-	].
+        binopChars := Scanner binarySelectorCharacters.
+        (self conform:[:eachChar | (binopChars includes:eachChar)]) ifTrue:[
+            ^ 1
+        ].
     ].
     ^ self occurrencesOf:$:
 
@@ -6936,11 +6937,11 @@
 !CharacterArray class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.526 2014-03-04 14:58:23 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.527 2014-03-04 23:01:45 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.526 2014-03-04 14:58:23 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.527 2014-03-04 23:01:45 cg Exp $'
 ! !