CharacterArray.st
branchjv
changeset 19811 65fec19facb0
parent 19707 8e312f358d84
parent 19785 c9672beda785
child 19863 513bd7237fe7
--- a/CharacterArray.st	Thu May 05 06:48:19 2016 +0200
+++ b/CharacterArray.st	Thu May 12 09:30:28 2016 +0200
@@ -107,19 +107,48 @@
 
 fromBytes:aByteCollection
     "return an instance of the receiver class,
-     taking untranslated bytes from the argument, aByteCollection.
+     taking untranslated bytes from the argument, aByteCollection
+     in most-significant first order.
+     Only useful, when reading twoByteStrings from external sources."
+
+    ^ self fromBytes:aByteCollection MSB:true
+
+    "
+     Unicode16String fromBytes:#[16r02 16r20]
+     Unicode16String fromBytes:#[16r02 16r20] MSB:true
+     Unicode16String fromBytes:#[16r02 16r20] MSB:false
+    "
+
+    "Modified: 30.6.1997 / 20:08:37 / cg"
+!
+
+fromBytes:aByteCollection MSB:msb
+    "return an instance of the receiver class,
+     taking untranslated bytes from the argument, aByteCollection
+     in the given byte order.
      Only useful, when reading twoByteStrings from external sources."
 
     |mySize nBytes newString dstIdx|
 
+    self assert:(self ~~ CharacterArray). "/ only works for concrete subclasses.
+
+    "/ the following is a quite inefficient implementation.
+    "/ consider rewriting, if heavily used.
     nBytes := aByteCollection size.
     mySize := self basicNew bitsPerCharacter.
     mySize == 16 ifTrue:[
 	newString := self uninitializedNew:(nBytes // 2).
 	dstIdx := 1.
-	aByteCollection pairWiseDo:[:hi :lo |
-	    newString at:dstIdx put:(Character value:(hi bitShift:8)+lo).
-	    dstIdx := dstIdx + 1
+	msb ifTrue:[
+	    aByteCollection pairWiseDo:[:hi :lo |
+		newString at:dstIdx put:(Character value:(hi bitShift:8)+lo).
+		dstIdx := dstIdx + 1
+	    ].
+	] ifFalse:[
+	    aByteCollection pairWiseDo:[:lo :hi |
+		newString at:dstIdx put:(Character value:(hi bitShift:8)+lo).
+		dstIdx := dstIdx + 1
+	    ].
 	].
 	^ newString.
     ].
@@ -142,7 +171,7 @@
     ^ (self uninitializedNew:sz) replaceFrom:1 to:sz with:aString startingAt:1
 
     "
-        Unicode16String fromString:'hello'
+	Unicode16String fromString:'hello'
     "
 !
 
@@ -363,7 +392,6 @@
     "
 ! !
 
-
 !CharacterArray class methodsFor:'pattern matching'!
 
 matchEscapeCharacter
@@ -769,7 +797,6 @@
     ^ Unicode32String
 ! !
 
-
 !CharacterArray methodsFor:'Compatibility-ANSI'!
 
 addLineDelimiters
@@ -791,18 +818,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.
 !
@@ -875,7 +902,7 @@
      '1 one two three four 5 five' asArrayOfSubstrings
      '1
 one
-        two three four 5 five' asArrayOfSubstrings
+	two three four 5 five' asArrayOfSubstrings
     "
 !
 
@@ -957,7 +984,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"
@@ -1087,8 +1114,8 @@
 !
 
 findDelimiters:delimiters startingAt:start
-    "Answer the index of the character within the receiver, starting at start, 
-     that matches one of the delimiters. 
+    "Answer the index of the character within the receiver, starting at start,
+     that matches one of the delimiters.
      If the receiver does not contain any of the delimiters, answer size + 1."
 
     |idx|
@@ -1241,9 +1268,9 @@
 
 substringsSeparatedBy:separatorCharacter
     "return a collection consisting of all words contained in the receiver.
-     Words are separated by the given separator character.   
+     Words are separated by the given separator character.
      This has been added for Squeak/Pharo compatibility.
-     (sigh: it is called #'subStrings:' in V'Age, 
+     (sigh: it is called #'subStrings:' in V'Age,
       and #'asCollectionOfSubstringsSeparatedBy' in ST/X) "
 
     ^ self asCollectionOfSubstringsSeparatedBy:separatorCharacter
@@ -1376,6 +1403,7 @@
 
     "
      'do you like %1 ?' bindWith:'smalltalk'
+     'do you like %(foo) ?' bindWithArguments:(Dictionary new at:'foo' put:'smalltalk'; yourself)
     "
 !
 
@@ -1513,7 +1541,7 @@
      and has been added for VisualAge compatibility."
 
     separatorCharacterOrString isCharacter ifTrue:[
-        ^ self asCollectionOfSubstringsSeparatedBy:separatorCharacterOrString
+	^ self asCollectionOfSubstringsSeparatedBy:separatorCharacterOrString
     ].
     ^ self asCollectionOfSubstringsSeparatedByAny:separatorCharacterOrString
 
@@ -1741,9 +1769,9 @@
     |mySize|
 
     (mySize := self size) >= 2 ifTrue:[
-        ((self first == quoteCharacter) and:[self last == quoteCharacter]) ifTrue:[
-            ^ self copyFrom:2 to:mySize-1
-        ].
+	((self first == quoteCharacter) and:[self last == quoteCharacter]) ifTrue:[
+	    ^ self copyFrom:2 to:mySize-1
+	].
     ].
     ^ self
 
@@ -1916,7 +1944,7 @@
 indexOfSeparatorOrEndStartingAt:startIndex
     "return the index of the next whitespace character,
      starting the search at startIndex, searching forward;
-     return the index of one behond the end of the receiver if no separator was found.
+     return the index of one beyond the end of the receiver if no separator was found.
      To extract the word, copy from startIndex to the returned index-1"
 
     |idx|
@@ -1933,6 +1961,7 @@
      'hello world ' indexOfSeparatorOrEndStartingAt:7
      'helloworld ' indexOfSeparatorOrEndStartingAt:7
      'helloworld' indexOfSeparatorOrEndStartingAt:7
+     'helloworld' indexOfSeparatorStartingAt:7
     "
 !
 
@@ -2345,13 +2374,22 @@
 hash_fnv1a
     "return an integer useful as a hash-key.
      This method uses the fnv-1a algorithm
-     (which is actually a very good one)"
-
-    |h|
+     (which is actually a very good one).
+     Attention: stops when a 0-codepoint is encountered
+		(for compatibility with the hash used by the VM)
+     Also: on 64bit CPUs, only small 4-byte hashvalues are returned,
+		(so hash values are independent from the architecture)"
+
+    |h byte|
 
     h := 2166136261.
     self do:[:eachChar |
-	h := h bitXor:(eachChar codePoint).
+	byte := eachChar codePoint.
+	byte == 0 ifTrue:[
+	    "/ stop
+	    ^ (h bitXor: (h >> 30)) bitAnd: 16r3FFFFFFF.
+	].
+	h := h bitXor:byte.
 	h := (h * 16777619) bitAnd:16rFFFFFFFF.
     ].
     "/ make sure, it fits into a smallInt
@@ -2543,11 +2581,11 @@
     mySize ~~ otherSize ifTrue:[^ false].
 
     1 to:mySize do:[:index |
-        c1 := self at:index.
-        c2 := aString at:index.
-        c1 ~~ c2 ifTrue:[
-            (c1 sameAs:c2) ifFalse:[^ false].
-        ]
+	c1 := self at:index.
+	c2 := aString at:index.
+	c1 ~~ c2 ifTrue:[
+	    (c1 sameAs:c2) ifFalse:[^ false].
+	]
     ].
     ^ true
 
@@ -2787,29 +2825,29 @@
 
     str := self string.
     str ~~ self ifTrue:[
-        "/ for text and other wrappers
-        ^ str asByteArray
+	"/ for text and other wrappers
+	^ str asByteArray
     ].
 
     "/ for real strings, a fallback
     sz := self size.
-    bytesPerCharacter := self bitsPerCharacter // 8.
+    bytesPerCharacter := self bytesPerCharacter.
     bytes := ByteArray new:(sz * bytesPerCharacter).
     idx := 1.
     self do:[:char |
-        |code|
-
-        code := char codePoint.
-        bytesPerCharacter == 2 ifTrue:[
-            bytes unsignedInt16At:idx put:code
-        ] ifFalse:[
-            bytesPerCharacter == 4 ifTrue:[
-                bytes unsignedInt32At:idx put:code
-            ] ifFalse:[
-                bytes at:idx put:code
-            ].
-        ].
-        idx := idx + bytesPerCharacter.
+	|code|
+
+	code := char codePoint.
+	bytesPerCharacter == 2 ifTrue:[
+	    bytes unsignedInt16At:idx put:code
+	] ifFalse:[
+	    bytesPerCharacter == 4 ifTrue:[
+		bytes unsignedInt32At:idx put:code
+	    ] ifFalse:[
+		bytes at:idx put:code
+	    ].
+	].
+	idx := idx + bytesPerCharacter.
     ].
     ^ bytes
 
@@ -2827,7 +2865,7 @@
 
     ba := self asByteArray. "/ native order
     UninterpretedBytes isBigEndian ~~ msb ifTrue:[
-        ba swapBytes
+	ba swapBytes
     ].
     ^ ba
 !
@@ -3194,17 +3232,17 @@
     bitsPerCharacter := newStr bitsPerCharacter.
 
     "/ handle the very seldom case of an uppercase char which needs
-    "/ more bits in its lowercase variant 
+    "/ more bits in its lowercase variant
     "/ (there are only a few of them)
 
     1 to:mySize do:[:i |
-        c := (self at:i) asLowercase.
-        (c bitsPerCharacter > bitsPerCharacter
-         and:[c stringSpecies ~= newStr stringSpecies]) ifTrue:[
-            newStr := c stringSpecies fromString:newStr.
-            bitsPerCharacter := newStr bitsPerCharacter.
-        ].
-        newStr at:i put:c
+	c := (self at:i) asLowercase.
+	(c bitsPerCharacter > bitsPerCharacter
+	 and:[c stringSpecies ~= newStr stringSpecies]) ifTrue:[
+	    newStr := c stringSpecies fromString:newStr.
+	    bitsPerCharacter := newStr bitsPerCharacter.
+	].
+	newStr at:i put:c
     ].
     ^ newStr
 
@@ -3381,10 +3419,10 @@
 !
 
 asSymbolIfInterned
-    "If a symbol with the receiver's characters is already known, return it. 
+    "If a symbol with the receiver's 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."
@@ -3393,12 +3431,12 @@
 
     str := self string.
     str == self ifTrue:[
-        "must be some kind of N-ByteString"
-        str := self asSingleByteStringIfPossible.
-        str == self ifTrue:[
-            "single byte string conversion is not possible"
-            ^ nil.
-        ].
+	"must be some kind of N-ByteString"
+	str := self asSingleByteStringIfPossible.
+	str == self ifTrue:[
+	    "single byte string conversion is not possible"
+	    ^ nil.
+	].
     ].
     ^ str asSymbolIfInterned
 
@@ -3449,16 +3487,16 @@
     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.
-            bitsPerCharacter := newStr bitsPerCharacter.
-        ].
-        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.
+	    bitsPerCharacter := newStr bitsPerCharacter.
+	].
+	newStr at:i put:c
     ].
     ^ newStr
 
@@ -3638,16 +3676,16 @@
     bitsPerCharacter := newStr bitsPerCharacter.
 
     "/ handle the very seldom case of a lowercase char which needs
-    "/ more bits in its uppercase variant 
+    "/ more bits in its uppercase variant
     "/ (there are only a few of them)
 
     1 to:mySize do:[:i |
-        c := (self at:i) asUppercase.
-        c bitsPerCharacter > bitsPerCharacter ifTrue:[
-            newStr := c stringSpecies fromString:newStr.
-            bitsPerCharacter := newStr bitsPerCharacter.
-        ].
-        newStr at:i put:c
+	c := (self at:i) asUppercase.
+	c bitsPerCharacter > bitsPerCharacter ifTrue:[
+	    newStr := c stringSpecies fromString:newStr.
+	    bitsPerCharacter := newStr bitsPerCharacter.
+	].
+	newStr at:i put:c
     ].
     ^ newStr
 
@@ -3797,7 +3835,7 @@
 
     n1 := n2 := maxLen // 2.
     maxLen odd ifTrue:[
-        n2 := n1 + 1
+	n2 := n1 + 1
     ].
     ^ (self copyFrom:1 to:n1) , (self copyFrom:sz - n2 + 1)
 
@@ -3983,11 +4021,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
 !
@@ -4164,6 +4202,15 @@
     "
 !
 
+asActionLinkTo:aBlock
+    "change the action block of all characters and colorize as a link.
+     Some widgets use this like a href if clicked onto the text
+     (for example, the system-browser's info at the bottom is such a widget)."
+
+    "/ the blue may become a user-setting some time later..
+    ^ (self actionForAll:aBlock) withColor:(Color blue)
+!
+
 colorizeAllWith:aColor
     "return a text object representing the receiver, but all colorized"
 
@@ -4287,12 +4334,16 @@
     "Created: / 13-12-1999 / 21:49:24 / cg"
 !
 
-withColor:aColor
+withColor:aColorOrColorSymbol
     "return a text object representing the receiver, but all colorized"
 
-    ^ self colorizeAllWith:aColor
-
-    "
+    aColorOrColorSymbol isSymbol ifTrue:[
+	^ self colorizeAllWith:(Color perform:aColorOrColorSymbol)
+    ].
+    ^ self colorizeAllWith:aColorOrColorSymbol
+
+    "
+     Transcript showCR:('hello' withColor:#red)
      Transcript showCR:('hello' withColor:Color red)
      Transcript showCR:('world' withColor:Color green darkened)
     "
@@ -4429,7 +4480,7 @@
 
     string := self string.
     string ~~ self ifTrue:[
-        ^ string utf8Encoded.
+	^ string utf8Encoded.
     ].
 
     ^ CharacterEncoderImplementations::ISO10646_to_UTF8 new encodeString:self
@@ -4449,25 +4500,25 @@
 
     string := self string.
     string ~~ self ifTrue:[
-        ^ string utf8EncodedOn:aStream.
+	^ string utf8EncodedOn:aStream.
     ].
 
     self containsNon7BitAscii ifTrue:[
-        aStream nextPutAllUtf8:self.
+	aStream nextPutAllUtf8:self.
     ] ifFalse:[
-        "speed up common case"
-        aStream nextPutAll:self.
+	"speed up common case"
+	aStream nextPutAll:self.
     ].
 
     "
      String streamContents:[:w|
-        'abcde1234' asUnicode32String utf8EncodedOn:w
+	'abcde1234' asUnicode32String utf8EncodedOn:w
      ].
      String streamContents:[:w|
-        'abcde1234' asUnicode32String utf8EncodedOn:w
+	'abcde1234' asUnicode32String utf8EncodedOn:w
      ].
      String streamContents:[:w|
-         'abcdeäöüß' asUnicode32String utf8EncodedOn:w
+	 'abcdeäöüß' asUnicode32String utf8EncodedOn:w
      ].
     "
 ! !
@@ -4536,7 +4587,7 @@
      This is usable with fileName pattern fields.
 
      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"
 
@@ -4545,9 +4596,9 @@
     matchers := self asCollectionOfSubstringsSeparatedBy:$;.
     withoutSeparators ifTrue:[ matchers := matchers collect:[:each | each withoutSeparators] ].
     ^ matchers
-        contains:[:aPattern |
-            aPattern match:aString caseSensitive:caseSensitive escapeCharacter:nil
-        ].
+	contains:[:aPattern |
+	    aPattern match:aString caseSensitive:caseSensitive escapeCharacter:nil
+	].
 
     "
      'f*' match:'foo'
@@ -4606,7 +4657,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"
 
@@ -4624,7 +4675,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"
 
@@ -4728,6 +4779,78 @@
     "Modified: 13.9.1997 / 06:31:22 / cg"
 !
 
+globPatternAsRegexPattern
+    "taking the receiver as a GLOB pattern,
+     return a corresponding regex pattern.
+     As regex does provide information about the matching substring,
+     it may be useful to apply a regex after a GLOB match,
+     in order to highlight matching substrings (eg. in a CodeView after a search).
+     If it turns out to be better, we may convert all GLOB searches to regex and use it right away.
+     (currently, it is not sure, if GLOB is not better for most simple searches, as they are encountered
+      in typical real life)"
+
+    ^ self species streamContents:[:s |
+	|addCharacter|
+
+	addCharacter :=
+	    [:ch |
+		ch isLetterOrDigit ifFalse:[
+		    s nextPut:$\.
+		].
+		s nextPut:ch
+	    ].
+
+	(String matchScanArrayFrom:self) do:[:matchEntry |
+	    matchEntry isCharacter ifTrue:[
+		addCharacter value:matchEntry
+	    ] ifFalse:[
+		matchEntry == #anyString ifTrue:[
+		    s nextPutAll:'.*'
+		] ifFalse:[
+		    matchEntry == #any ifTrue:[
+			s nextPut:$.
+		    ] ifFalse:[
+			matchEntry isString ifTrue:[
+			    |set min max|
+
+			    s nextPut:$[.
+			    set := matchEntry copy sort.
+			    min := set min.
+			    max := set max.
+			    set asSet = (min to:max) asSet ifTrue:[
+				addCharacter value:min.
+				s nextPut:$-.
+				addCharacter value:max.
+			    ] ifFalse:[
+				set do:addCharacter.
+			    ].
+			    s nextPut:$].
+			] ifFalse:[
+			    self halt.
+			].
+		    ].
+		].
+	    ]
+	].
+    ].
+
+    "
+     'hello' globPatternAsRegexPattern
+     'hello*' globPatternAsRegexPattern
+     '*hello*' globPatternAsRegexPattern
+     'h###' globPatternAsRegexPattern
+     'h[0-9]' globPatternAsRegexPattern
+     'h[0-9][0-9][0-9]' globPatternAsRegexPattern
+     'h[0-9]*' globPatternAsRegexPattern
+     'h[-+]*' globPatternAsRegexPattern
+
+     'hello world' matches:'h*w'
+     'hello world' matchesRegex:('h*w' globPatternAsRegexPattern)
+     'hello world' matches:'h*d'
+     'hello world' matchesRegex:('h*d' globPatternAsRegexPattern)
+    "
+!
+
 includesMatchString:matchString
     "like includesString, but allowing GLOB match patterns.
      find matchstring; if found, return true, otherwise return false.
@@ -4752,7 +4875,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"
 
@@ -4896,7 +5019,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"
 
@@ -4990,13 +5113,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 caseSensitive:ignoreCase not
-        escapeCharacter:(self class matchEscapeCharacter)
+	match:aString from:start to:stop caseSensitive:ignoreCase not
+	escapeCharacter:(self class matchEscapeCharacter)
 
     "
      '*ute*' match:'12345COMPUTER' from:1 to:5 ignoreCase:true
@@ -5041,7 +5164,7 @@
      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"
 
@@ -5061,14 +5184,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
+	]
      ].
     "
 
@@ -5083,7 +5206,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"
 
@@ -5102,14 +5225,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
+	]
      ].
     "
 
@@ -5167,13 +5290,13 @@
     "Test if the receiver matches a regex.
      May raise RxParser>>regexErrorSignal or child signals.
      This is a part of the Regular Expression Matcher package,
-        (c) 1996, 1999 Vassili Bykov.
+	(c) 1996, 1999 Vassili Bykov.
      Refer to `documentation' protocol of RxParser class for details."
 
     aBoolean ifFalse:[
-        ^ self matchesRegexIgnoringCase:regexString
+	^ self matchesRegexIgnoringCase:regexString
     ] ifTrue:[
-        ^ self matchesRegex:regexString
+	^ self matchesRegex:regexString
     ].
 
     "
@@ -5213,9 +5336,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
     ]
 
     "
@@ -5239,11 +5362,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    '
@@ -5272,25 +5395,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
@@ -5324,7 +5447,7 @@
 !
 
 paddedTo:newSize
-     "return a new string consisting of the receivers characters,
+     "return a new string consisting of the receiver's characters,
      plus spaces up to length.
      If the receiver's size is equal or greater than the length argument,
      the original receiver is returned unchanged."
@@ -5349,54 +5472,54 @@
 
     firstChar := (self at:1) asLowercase.
     ((firstChar isVowel and:[firstChar ~~ $u]) or:[firstChar == $x]) ifTrue:[
-        ^ 'an'
+	^ 'an'
     ].
 
     (self size >= 3) ifTrue:[
-        secondChar := (self at:2) asLowercase.
-
-        "/ may need more here...
-        ( #('rb') includes:(String with:firstChar with:secondChar)) ifTrue:[
-            ^ 'an'
-        ].
-
-        thirdChar := (self at:3) asLowercase.
-
-        (firstChar isVowel not
-        and:[(secondChar isVowel or:[secondChar == $y]) not
-        and:[thirdChar isVowel not ]]) ifTrue:[
-            "/ exceptions: 3 non-vowels in a row: looks like an abbreviation
-            (self size > 4) ifTrue:[
-                (firstChar == $s) ifTrue:[
-                    ((secondChar == $c and:[thirdChar == $r])
-                    or:[ (secondChar == $t and:[thirdChar == $r]) ]) ifTrue:[
-                        (self at:4) isVowel ifTrue:[
-                            ^ 'a'
-                        ]
-                    ]
-                ].
-            ].
-            "/ an abbreviation; treat x, s as vowels
-            (firstChar == $x or:[ firstChar == $s ]) ifTrue:[^ 'an'].
-        ]
+	secondChar := (self at:2) asLowercase.
+
+	"/ may need more here...
+	( #('rb') includes:(String with:firstChar with:secondChar)) ifTrue:[
+	    ^ 'an'
+	].
+
+	thirdChar := (self at:3) asLowercase.
+
+	(firstChar isVowel not
+	and:[(secondChar isVowel or:[secondChar == $y]) not
+	and:[thirdChar isVowel not ]]) ifTrue:[
+	    "/ exceptions: 3 non-vowels in a row: looks like an abbreviation
+	    (self size > 4) ifTrue:[
+		(firstChar == $s) ifTrue:[
+		    ((secondChar == $c and:[thirdChar == $r])
+		    or:[ (secondChar == $t and:[thirdChar == $r]) ]) ifTrue:[
+			(self at:4) isVowel ifTrue:[
+			    ^ 'a'
+			]
+		    ]
+		].
+	    ].
+	    "/ an abbreviation; treat x, s as vowels
+	    (firstChar == $x or:[ firstChar == $s ]) ifTrue:[^ 'an'].
+	]
     ].
     ^ 'a'
 
     "
-        'uboot' article.
-        'xmas' article. 
-        'alarm' article.
-        'baby' article. 
-        'sql' article.  
-        'scr' article.   
-        'screen' article. 
-        'scrollbar' article.  
-        'scrs' article.   
-        'cvs' article.    
-        'cvssource' article.
-        'symbol' article.
-        'string' article.
-        'rbparser' article.
+	'uboot' article.
+	'xmas' article.
+	'alarm' article.
+	'baby' article.
+	'sql' article.
+	'scr' article.
+	'screen' article.
+	'scrollbar' article.
+	'scrs' article.
+	'cvs' article.
+	'cvssource' article.
+	'symbol' article.
+	'string' article.
+	'rbparser' article.
     "
 
     "Modified (comment): / 01-05-2016 / 10:57:25 / cg"
@@ -5567,12 +5690,12 @@
     |string max|
 
     (string := self string) ~~ self ifTrue:[
-        ^ string bitsPerCharacter
+	^ string bitsPerCharacter
     ].
 
     max := 8.
     self do:[:eachCharacter |
-        max := max max:(eachCharacter bitsPerCharacter)
+	max := max max:(eachCharacter bitsPerCharacter)
     ].
     ^ max
 
@@ -5582,6 +5705,30 @@
     "
 !
 
+bytesPerCharacter
+    "return the underlying string's required
+     bytesPerCharacter
+     (i.e. is it a regular String or a TwoByteString)"
+
+    |string max|
+
+    (string := self string) ~~ self ifTrue:[
+	^ string bytesPerCharacter
+    ].
+
+    max := 1.
+    self do:[:eachCharacter |
+	max := max max:(eachCharacter bytesPerCharacter)
+    ].
+    ^ max
+
+    "
+     'hello' bytesPerCharacter
+     'hello' asUnicode16String bytesPerCharacter
+     'hello' asText allBold bytesPerCharacter
+    "
+!
+
 containsNon8BitElements
     "return true, if the underlying string contains elements larger than a single byte"
 
@@ -5589,9 +5736,9 @@
 
     sz := self size.
     1 to:sz do:[:idx|
-        (self at:idx) codePoint > 16rFF ifTrue:[
-            ^ true.
-        ].
+	(self at:idx) codePoint > 16rFF ifTrue:[
+	    ^ true.
+	].
     ].
     ^ false.
 !
@@ -5766,8 +5913,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
 
@@ -5852,7 +5999,6 @@
     "Modified: 17.4.1997 / 12:50:23 / cg"
 ! !
 
-
 !CharacterArray methodsFor:'special string converting'!
 
 asUnixFilenameString
@@ -5950,97 +6096,97 @@
     stop := self size.
     start := 1.
     [start <= stop] whileTrue:[
-        idx := self indexOf:escapeCharacter startingAt:start.
-        (idx == 0 or:[idx == stop]) ifTrue:[
-            aStream nextPutAll:self startingAt:start to:stop.
-            ^ self.
-        ].
-        "found an escapeCharacter"
-        aStream nextPutAll:self startingAt:start to:(idx - 1).
-        next := self at:(idx + 1).
-        (next == escapeCharacter) ifTrue:[
-            aStream nextPut:escapeCharacter.
-        ] ifFalse:[
-            next == $< ifTrue:[
-                idx2 := self indexOf:$> startingAt:idx+2.
-                key := self copyFrom:idx+2 to:idx2-1.
-                idx := idx2 - 1.
-                key := key asSymbolIfInterned.
-                (#(cr tab nl return lf ff null) includesIdentical:key) ifTrue:[
-                    aStream nextPut:(Character perform:key).
-                ].
-            ] ifFalse:[
-                next isDigit ifTrue:[
-                    v := argArrayOrDictionary at:(next digitValue) ifAbsent:''
-                ] ifFalse:[
-                    next == $( ifTrue:[
-                        idx2 := self indexOf:$) startingAt:idx+2.
-                        key := self copyFrom:idx+2 to:idx2-1.
-                        idx := idx2 - 1.
-                        (argArrayOrDictionary includesKey:key) ifTrue:[
-                            v := argArrayOrDictionary at:key
-                        ] ifFalse:[
-                            key := key asSymbolIfInterned ? key.
-                            (argArrayOrDictionary includesKey:key) ifTrue:[
-                                v := argArrayOrDictionary at:key
-                            ] ifFalse:[
-                                (key size == 1 and:[ argArrayOrDictionary includesKey:(key at:1)]) ifTrue:[
-                                    v := argArrayOrDictionary at:(key at:1)
-                                ] ifFalse:[
-                                    key isNumeric ifTrue:[
-                                        key := Integer readFrom:key onError:nil.
-                                    ].
-                                    v := argArrayOrDictionary at:key ifAbsent:''
-                                ]
-                            ].
-                        ].
-                    ] ifFalse:[
-                        (next isLetter and:[argArrayOrDictionary isSequenceable not "is a Dictionary"]) ifTrue:[
-                            "so next is a non-numeric single character."
-                            v := argArrayOrDictionary
-                                    at:next
-                                    ifAbsent:[
-                                        "try symbol instead of character"
-                                        argArrayOrDictionary
-                                            at:next asSymbol
-                                            ifAbsent:[String with:escapeCharacter with:next].
-                                 ].
-                        ] ifFalse:[
-                            v := String with:$% with:next.
-                        ].
-                    ]
-                ].
-                "/ v notNil ifTrue:[
-                    v isBlock ifTrue:[
-                        v := v value
-                    ].
-
-                    v printOn:aStream.
-                "/ ].
-            ]
-        ].
-        start := idx + 2
+	idx := self indexOf:escapeCharacter startingAt:start.
+	(idx == 0 or:[idx == stop]) ifTrue:[
+	    aStream nextPutAll:self startingAt:start to:stop.
+	    ^ self.
+	].
+	"found an escapeCharacter"
+	aStream nextPutAll:self startingAt:start to:(idx - 1).
+	next := self at:(idx + 1).
+	(next == escapeCharacter) ifTrue:[
+	    aStream nextPut:escapeCharacter.
+	] ifFalse:[
+	    next == $< ifTrue:[
+		idx2 := self indexOf:$> startingAt:idx+2.
+		key := self copyFrom:idx+2 to:idx2-1.
+		idx := idx2 - 1.
+		key := key asSymbolIfInterned.
+		(#(cr tab nl return lf ff null) includesIdentical:key) ifTrue:[
+		    aStream nextPut:(Character perform:key).
+		].
+	    ] ifFalse:[
+		next isDigit ifTrue:[
+		    v := argArrayOrDictionary at:(next digitValue) ifAbsent:''
+		] ifFalse:[
+		    next == $( ifTrue:[
+			idx2 := self indexOf:$) startingAt:idx+2.
+			key := self copyFrom:idx+2 to:idx2-1.
+			idx := idx2 - 1.
+			(argArrayOrDictionary includesKey:key) ifTrue:[
+			    v := argArrayOrDictionary at:key
+			] ifFalse:[
+			    key := key asSymbolIfInterned ? key.
+			    (argArrayOrDictionary includesKey:key) ifTrue:[
+				v := argArrayOrDictionary at:key
+			    ] ifFalse:[
+				(key size == 1 and:[ argArrayOrDictionary includesKey:(key at:1)]) ifTrue:[
+				    v := argArrayOrDictionary at:(key at:1)
+				] ifFalse:[
+				    key isNumeric ifTrue:[
+					key := Integer readFrom:key onError:nil.
+				    ].
+				    v := argArrayOrDictionary at:key ifAbsent:''
+				]
+			    ].
+			].
+		    ] ifFalse:[
+			(next isLetter and:[argArrayOrDictionary isSequenceable not "is a Dictionary"]) ifTrue:[
+			    "so next is a non-numeric single character."
+			    v := argArrayOrDictionary
+				    at:next
+				    ifAbsent:[
+					"try symbol instead of character"
+					argArrayOrDictionary
+					    at:next asSymbol
+					    ifAbsent:[String with:escapeCharacter with:next].
+				 ].
+			] ifFalse:[
+			    v := String with:$% with:next.
+			].
+		    ]
+		].
+		"/ v notNil ifTrue:[
+		    v isBlock ifTrue:[
+			v := v value
+		    ].
+
+		    v printOn:aStream.
+		"/ ].
+	    ]
+	].
+	start := idx + 2
     ].
 
     "
      String streamContents:[:s|
-        'hello %1' expandPlaceholders:$% with:#('world') on:s.
-        s cr.
-        'hello $1; how is $2' expandPlaceholders:$$ with:#('world' 'this') on:s.
-        s cr.
-        'hello %2; how is %1' expandPlaceholders:$% with:#('world' 'this') on:s.
-        s cr.
-        '%1 plus %2 gives %3 ' expandPlaceholders:$% with:#(4 5 9) on:s.
-        s cr.
-        '%%(1)0 gives %(1)0' expandPlaceholders:$% with:#(123) on:s.
-        s cr.
-        '%%10 gives %10' expandPlaceholders:$% with:#(123) on:s.
-        s cr.
-        '%%(10) gives %(10) %<cr>%<tab>next line' expandPlaceholders:$% with:#(123) on:s.
-        s cr.
-        '%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
-        s cr.
-        '|%%<tab>|%%1|%%<cr>| gives |%<tab>|%1|%<cr>|' expandPlaceholders:$% with:#(foo) on:s.
+	'hello %1' expandPlaceholders:$% with:#('world') on:s.
+	s cr.
+	'hello $1; how is $2' expandPlaceholders:$$ with:#('world' 'this') on:s.
+	s cr.
+	'hello %2; how is %1' expandPlaceholders:$% with:#('world' 'this') on:s.
+	s cr.
+	'%1 plus %2 gives %3 ' expandPlaceholders:$% with:#(4 5 9) on:s.
+	s cr.
+	'%%(1)0 gives %(1)0' expandPlaceholders:$% with:#(123) on:s.
+	s cr.
+	'%%10 gives %10' expandPlaceholders:$% with:#(123) on:s.
+	s cr.
+	'%%(10) gives %(10) %<cr>%<tab>next line' expandPlaceholders:$% with:#(123) on:s.
+	s cr.
+	'%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
+	s cr.
+	'|%%<tab>|%%1|%%<cr>| gives |%<tab>|%1|%<cr>|' expandPlaceholders:$% with:#(foo) on:s.
      ]
     "
 
@@ -6052,7 +6198,7 @@
      dict at:$a put:'AAAAA'.
      dict at:$b put:[ Time now ].
      String streamContents:[:s|
-         'hello $1 $a $b' expandPlaceholders:$$ with:dict on:s.
+	 'hello $1 $a $b' expandPlaceholders:$$ with:dict on:s.
      ].
     "
 
@@ -6063,10 +6209,10 @@
      dict at:'time' put:[Time now printString].
      dict at:'date' put:[Date today printString].
      String streamContents:[:s|
-         'it is $(time) $(date)' expandPlaceholders:$$ with:dict on:s.
+	 'it is $(time) $(date)' expandPlaceholders:$$ with:dict on:s.
      ].
     "
-    
+
     "Modified: / 18-11-2010 / 15:43:28 / cg"
 !
 
@@ -6075,13 +6221,13 @@
      replaced by corresponding arguments' printStrings from the argArrayOrDictionary.
      I.e. 'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this') results
      in the new string 'hello world; how is this'.
-     
+
      As an extension, the argument may also be a dictionary, providing
      values for symbolic keys.
      In this case, %a .. %z and %(...) are also allowed.
      (%1..%9 require a numeric key in the dictionary, however)
      Also, the values in argArrayOrDictionary may be blocks.
-     
+
      To get a '%' character, use a '%%'-escape.
      To get an integer-indexed placeHolder followed by another digit,
      or an index > 9, you must use %(digit).
@@ -6093,7 +6239,6 @@
     self expandPlaceholdersWith:argArrayOrDictionary on:stream.
     ^ stream contents.
 
-
     "
      'hello %1' expandPlaceholdersWith:#('world')
      'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this')
@@ -6105,6 +6250,10 @@
      '%test gives %1' expandPlaceholdersWith:#(123)
      'bla %1 bla' expandPlaceholdersWith:{ 'hello' allBold }
      'bla %1 bla' expandPlaceholdersWith:{ 'hello' }
+     ('bla %1 bla' withColor:Color red)
+	expandPlaceholdersWith:{ 'hello' }
+     ('bla %1 bla' withColor:Color red)
+	expandPlaceholdersWith:{ 'hello' withColor:Color blue }
     "
 
     "
@@ -6144,21 +6293,21 @@
 
     "
      String streamContents:[:s|
-        'hello %1' expandPlaceholdersWith:#('world') on:s.
-        s cr.
-        'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this') on:s.
-        s cr.
-        'hello %2; how is %1' expandPlaceholdersWith:#('world' 'this') on:s.
-        s cr.
-        '%1 plus %2 gives %3 ' expandPlaceholdersWith:#(4 5 9) on:s.
-        s cr.
-        '%%(1)0 gives %(1)0' expandPlaceholdersWith:#(123) on:s.
-        s cr.
-        '%%10 gives %10' expandPlaceholdersWith:#(123) on:s.
-        s cr.
-        '%%(10) gives %(10) %<cr>%<tab>next line' expandPlaceholdersWith:#(123) on:s.
-        s cr.
-        '%test gives %1' expandPlaceholdersWith:#(123) on:s.
+	'hello %1' expandPlaceholdersWith:#('world') on:s.
+	s cr.
+	'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this') on:s.
+	s cr.
+	'hello %2; how is %1' expandPlaceholdersWith:#('world' 'this') on:s.
+	s cr.
+	'%1 plus %2 gives %3 ' expandPlaceholdersWith:#(4 5 9) on:s.
+	s cr.
+	'%%(1)0 gives %(1)0' expandPlaceholdersWith:#(123) on:s.
+	s cr.
+	'%%10 gives %10' expandPlaceholdersWith:#(123) on:s.
+	s cr.
+	'%%(10) gives %(10) %<cr>%<tab>next line' expandPlaceholdersWith:#(123) on:s.
+	s cr.
+	'%test gives %1' expandPlaceholdersWith:#(123) on:s.
      ]
     "
 
@@ -6170,7 +6319,7 @@
      dict at:$a put:'AAAAA'.
      dict at:$b put:[ Time now ].
      String streamContents:[:s|
-         'hello %1 %a %b' expandPlaceholdersWith:dict on:s.
+	 'hello %1 %a %b' expandPlaceholdersWith:dict on:s.
      ].
     "
 
@@ -6383,13 +6532,13 @@
      Typically used with space as replacementCharacter"
 
     ^ self species streamContents:[:s |
-        self do:[:ch |
-            ch isSeparator ifTrue:[
-                s nextPut:replacementCharacter
-            ] ifFalse:[    
-                s nextPut:ch.
-            ]
-        ]
+	self do:[:ch |
+	    ch isSeparator ifTrue:[
+		s nextPut:replacementCharacter
+	    ] ifFalse:[
+		s nextPut:ch.
+	    ]
+	]
     ]
 
     "
@@ -6409,8 +6558,8 @@
      Notice: if the receiver does not contain any tabs, it is returned unchanged;
      otherwise a new string is returned.
      Limitation: only the very first spaces are replaced
-                 (i.e. if the receiver contains newLine characters,
-                  no tabs are inserted after those lineBreaks)"
+		 (i.e. if the receiver contains newLine characters,
+		  no tabs are inserted after those lineBreaks)"
 
     |idx   "{ SmallInteger }"
      nTabs "{ SmallInteger }"
@@ -6454,19 +6603,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"
@@ -6495,19 +6644,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
+	    ].
+	]
     ].
 
     self isText ifTrue:[ 
@@ -6520,26 +6669,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
 
@@ -6553,19 +6702,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-05-1996 / 13:05:10 / cg"
@@ -6807,7 +6956,7 @@
      Otherwise return the receiver"
 
     (self startsWith:aString) ifTrue:[
-        ^ self copyButFirst:aString size
+	^ self copyFrom:aString size+1
     ].
     ^ self
 
@@ -6884,7 +7033,7 @@
      Otherwise return the receiver"
 
     (self endsWith:aString) ifTrue:[
-        ^ self copyButLast:aString size
+	^ self copyFrom:1 to:(self size - aString size)
     ].
     ^ self
 
@@ -6914,7 +7063,6 @@
     "
 ! !
 
-
 !CharacterArray methodsFor:'substring searching'!
 
 findRangeOfString:subString
@@ -7049,16 +7197,16 @@
     "
 !
 
-indexOfString:aString startingAt:startIndex 
+indexOfString:aString startingAt:startIndex
     "VSE and V'age compatibility"
     "find a substring. If found, return the index; if not found, return 0."
 
     ^ self indexOfSubCollection:aString startingAt:startIndex ifAbsent:[0]
 !
 
-indexOfString:aString startingAt:startIndex ifAbsent:exceptionalValue 
+indexOfString:aString startingAt:startIndex ifAbsent:exceptionalValue
     "VSE and V'age compatibility"
-    "find a substring. 
+    "find a substring.
      If found, return the index; if not found, the value from exceptionalValue."
 
     ^ self indexOfSubCollection:aString startingAt:startIndex ifAbsent:exceptionalValue
@@ -7215,7 +7363,7 @@
 
 lastIndexOfString:aString
     "VSE and V'age compatibility"
-    "find the last occurrence of substring. 
+    "find the last occurrence of substring.
      If found, return the index; if not found, return 0."
 
     ^ self lastIndexOfSubCollection:aString startingAt:(self size-aString size+1) ifAbsent:[0]
@@ -7229,20 +7377,20 @@
 
 lastIndexOfString:aString ifAbsent:exceptionValue
     "VSE and V'age compatibility"
-    "find the last occurrence of substring. 
+    "find the last occurrence of substring.
      If found, return the index; if not found, return 0."
 
     ^ self lastIndexOfSubCollection:aString startingAt:(self size-aString size+1) ifAbsent:exceptionValue
 
     " 123456789012
      'abcdefabcdef' lastIndexOfString:'abc' ifAbsent:[999]
-     'abcdefabcdef' lastIndexOfString:'xxx' ifAbsent:[999] 
+     'abcdefabcdef' lastIndexOfString:'xxx' ifAbsent:[999]
     "
 !
 
 lastIndexOfString:aString startingAt:startIndex
     "VSE and V'age compatibility"
-    "find the last occurrence of a substring. 
+    "find the last occurrence of a substring.
      If found, return the index; if not found, return 0."
 
     ^ self lastIndexOfSubCollection:aString startingAt:startIndex ifAbsent:[0]
@@ -7255,7 +7403,7 @@
 
 lastIndexOfString:aString startingAt:startIndex ifAbsent:exceptionValue
     "VSE and V'age compatibility"
-    "find the last occurrence of a substring. 
+    "find the last occurrence of a substring.
      If found, return the index; if not found, return 0."
 
     ^ self lastIndexOfSubCollection:aString startingAt:startIndex ifAbsent:exceptionValue
@@ -7293,10 +7441,10 @@
     |binopChars|
 
     (self size <= Method maxBinarySelectorSize) ifTrue:[
-        binopChars := Method binarySelectorCharacters.
-        (self conform:[:eachChar | (binopChars includes:eachChar)]) ifTrue:[
-            ^ 1
-        ].
+	binopChars := Method binarySelectorCharacters.
+	(self conform:[:eachChar | (binopChars includes:eachChar)]) ifTrue:[
+	    ^ 1
+	].
     ].
     ^ self occurrencesOf:$:
 
@@ -7319,26 +7467,26 @@
 characterSize
     "answer the size in bits of my largest character (actually only 7, 8, 16 or 32)"
 
-    |string max    
+    |string max
      sz "{ Class:SmallInteger}" |
 
     (string := self string) ~~ self ifTrue:[
-        ^ string characterSize.
+	^ string characterSize.
     ].
 
     sz := self size.
     max := 7.
     1 to:sz do:[:idx |
-        |thisSize|
-
-        thisSize := (self at:idx) characterSize.
-        thisSize > max ifTrue:[
-            max := thisSize.
-            max == 32 ifTrue:[
-                "shortcut: we know, that max size is 32"
-                ^ 32.
-            ].
-        ].
+	|thisSize|
+
+	thisSize := (self at:idx) characterSize.
+	thisSize > max ifTrue:[
+	    max := thisSize.
+	    max == 32 ifTrue:[
+		"shortcut: we know, that max size is 32"
+		^ 32.
+	    ].
+	].
     ].
 
     ^ max.
@@ -7365,13 +7513,13 @@
      sz "{ Class:SmallInteger }"|
 
     (string := self string) ~~ self ifTrue:[
-        ^ string containsNon7BitAscii
+	^ string containsNon7BitAscii
     ].
     sz := self size.
     1 to:sz do:[:idx|
-        (self at:idx) codePoint > 16r7F ifTrue:[
-            ^ true.
-        ].
+	(self at:idx) codePoint > 16r7F ifTrue:[
+	    ^ true.
+	].
     ].
     ^ false.
 
@@ -7460,16 +7608,16 @@
 
     state := #initial.
     self do:[:char |
-        (state == #initial or:[ state == #gotColon]) ifTrue:[
-            (char isLetterOrUnderline) ifFalse:[^ false].
-            state := #gotCharacter.
-        ] ifFalse:[
-            char == $: ifTrue:[
-                state := #gotColon.
-            ] ifFalse:[
-                (char isLetterOrDigit or:[char == $_]) ifFalse:[^ false].
-            ].
-        ].
+	(state == #initial or:[ state == #gotColon]) ifTrue:[
+	    (char isLetterOrUnderline) ifFalse:[^ false].
+	    state := #gotCharacter.
+	] ifFalse:[
+	    char == $: ifTrue:[
+		state := #gotColon.
+	    ] ifFalse:[
+		(char isLetterOrDigit or:[char == $_]) ifFalse:[^ false].
+	    ].
+	].
     ].
     ^ state == #gotColon.
 
@@ -7587,12 +7735,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.
@@ -7609,11 +7757,11 @@
 
 isWideString
     "true if I require more than one byte per character"
-    
+
     |string|
 
     (string := self string) ~~ self ifTrue:[
-        ^ string isWideString.
+	^ string isWideString.
     ].
     ^ self contains:[:aCharacter | aCharacter codePoint > 16rFF].
 !