Cherry-picked changes from eXept, part 2 jv
authorJan Vrany <jan.vrany@labware.com>
Mon, 31 Aug 2020 12:01:25 +0100
branchjv
changeset 25416 c9cd91278d66
parent 25415 4ea1fe7c363f
child 25417 fda845cb1c37
Cherry-picked changes from eXept, part 2 ...from commit a6b6dda4caff: * CharacterArray.st * String.st * SequenceableCollection.st
CharacterArray.st
SequenceableCollection.st
String.st
--- a/CharacterArray.st	Mon Aug 31 11:59:30 2020 +0100
+++ b/CharacterArray.st	Mon Aug 31 12:01:25 2020 +0100
@@ -22,7 +22,7 @@
 	instanceVariableNames:''
 	classVariableNames:'DecoderTables DecodingFailedSignal EncoderTables
 		EncodingFailedSignal PreviousMatches UnicodeDenormalizationMap
-		UnicodeNormalizationMap'
+		UnicodeNormalizationMap DeadKeyMap'
 	poolDictionaries:''
 	category:'Collections-Text'
 !
@@ -77,6 +77,27 @@
         is treated as raw data, and the strings have to be copied/shuffled around only,
         without any real processing on it.
 
+    [about hashing:]
+        the ST/X VM uses the fnv1 hash (*) to quickly retrieve symbols,
+        This has only 1 collision in my current systm with 66k symbols.
+
+        To try, evaluate:
+            ((Symbol allInstances collect:#hash_fnv1a as:Bag)
+                valuesAndCountsSelect:[:h :cnt | cnt > 1]) size
+        in contrast, java hash is much worse (18 collisions):
+            ((Symbol allInstances collect:#hash_java as:Bag)
+                valuesAndCountsSelect:[:h :cnt | cnt > 1]) size
+        and hash_sdbm hash is even better (0 collisions),
+        but slightly slower:
+            ((Symbol allInstances collect:#hash_sdbm as:Bag)
+                valuesAndCountsSelect:[:h :cnt | cnt > 1]) size
+        we could use CRC32 (also with 0 collisions), 
+        but that is slower on machines without CRC instruction:
+            ((Symbol allInstances collect:[:s | CRC32Stream hashValueOf:s] as:Bag)
+                valuesAndCountsSelect:[:h :cnt | cnt > 1]) size
+
+        (*) slightly modified to return a 31bit positive number, eg. a SmallInt in 32bit systems.
+
     [author:]
         Claus Gittinger
 
@@ -93,7 +114,7 @@
         DecodingFailedSignal := DecodingError.
         DecodingFailedSignal notifierString:'error during decode'.
 
-        EncodingFailedSignal :=EncodingError.
+        EncodingFailedSignal := EncodingError.
         EncodingFailedSignal notifierString:'error during encode'.
     ]
 
@@ -101,7 +122,8 @@
      CharacterArray initialize
     "
 
-    "Modified: 3.8.1997 / 18:15:59 / cg"
+    "Modified: / 03-08-1997 / 18:15:59 / cg"
+    "Modified (format): / 16-01-2018 / 18:57:10 / stefan"
 ! !
 
 !CharacterArray class methodsFor:'instance creation'!
@@ -179,11 +201,13 @@
 
     "
         Unicode16String fromString:'hello'
+        String fromString:'hello' asUnicode16String
+        Unicode16String fromString:'hello' asUnicode16String
     "
 !
 
 fromStringCollection:aCollectionOfStrings
-    "return new string formed by concatenating a copy of the argument, aString"
+    "return a new string formed by concatenating each in aCollectionOfStrings"
 
     ^ self fromStringCollection:aCollectionOfStrings separatedBy:''
 
@@ -191,11 +215,13 @@
      String fromStringCollection:#('hello' 'world' 'how' 'about' 'this')
     "
 
-    "Created: 20.11.1995 / 15:26:59 / cg"
+    "Created: / 20-11-1995 / 15:26:59 / cg"
+    "Modified (comment): / 05-06-2019 / 14:28:35 / Claus Gittinger"
 !
 
 fromStringCollection:aCollectionOfStrings separatedBy:aSeparatorString
-    "return new string formed by concatenating a copy of the argument, aString"
+    "return a new string formed by concatenating each in aCollectionOfStrings
+     separating them by aSeparatorString"
 
     |stream|
 
@@ -217,10 +243,12 @@
      Text fromStringCollection:{'hello'. 'world'. 'how' allBold. 'about'. 'this'. 'äöü'} separatedBy:'Ƞ'
     "
 
-    "Created: 20.11.1995 / 15:32:17 / cg"
+    "Created: / 20-11-1995 / 15:32:17 / cg"
+    "Modified (comment): / 05-06-2019 / 14:27:46 / Claus Gittinger"
 !
 
 fromUTF8Bytes:aByteCollection
+    <resource: #obsolete>
     "return a new string which represents the characters as decoded
      from the utf8 encoded bytes, aByteCollection.
      Returns either a normal String, or a TwoByteString instance.
@@ -229,21 +257,7 @@
 
     ^ self decodeFromUTF8:aByteCollection.
 
-    "
-     CharacterArray fromUTF8Bytes:#[ 16r41 16r42 ]
-     CharacterArray fromUTF8Bytes:#[ 16rC1 16r02 ]
-     CharacterArray fromUTF8Bytes:#[ 16rE0 16r81 16r02 ]
-     CharacterArray fromUTF8Bytes:#[ 16rEF 16rBF 16rBF ]
-
-   rfc2279 examples:
-     CharacterArray fromUTF8Bytes:#[ 16r41 16rE2 16r89 16rA2 16rCE 16r91 16r2E ]
-     CharacterArray fromUTF8Bytes:#[ 16rED 16r95 16r9C 16rEA 16rB5 16rAD 16rEC 16r96 16rB4 ]
-     CharacterArray fromUTF8Bytes:#[ 16rE6 16r97 16rA5 16rE6 16r9C 16rAC 16rE8 16rAA 16r9E ]
-
-   invalid:
-     CharacterArray fromUTF8Bytes:#[ 16rC0 16r80 ]
-     CharacterArray fromUTF8Bytes:#[ 16rE0 16r80 16r80 ]
-    "
+    "Modified (comment): / 07-02-2017 / 17:32:38 / stefan"
 !
 
 new
@@ -252,24 +266,29 @@
     ^ self basicNew:0
 !
 
-readSmalltalkStringFrom:aStreamOrString onError:exceptionBlock
+readSmalltalkStringFrom:aStreamOrString keepCRs:keepCRs onError:exceptionBlock
     "read & return the next String from the (character-)stream aStream;
      skipping all whitespace first; return the value of exceptionBlock,
      if no string can be read. The sequence of characters as read from the
-     stream must be one as stored via storeOn: or storeString."
-
-    |str collected char|
+     stream must be one as stored via storeOn: or storeString.
+     If keepCRs is true, CRLF is kept as is.
+     A variant of this code is also found in the Scanner class (libcomp);
+     however, libcomp is optional, whereas this is always present,
+     and string reading is needed for resource file and config file parsing (sigh)"
+
+    |str collected char withCEscapes|
 
     str := aStreamOrString readStream.
-
     "skip whiteSpace"
     str skipSeparators.
 
+    (withCEscapes := (str peekOrNil == $c)) ifTrue:[
+        str next.
+    ].
     (str peekOrNil == $') ifTrue:[
         str next.
         collected := self writeStream.
-        [str atEnd] whileFalse:[
-            char := str next.
+        [(char := str nextOrNil) notNil] whileTrue:[
             char == $' ifTrue:[
                 "/ look for another quote
                 str peekOrNil ~~ $' ifTrue:[
@@ -279,9 +298,31 @@
                 "eat doubled quote"
                 str next.
             ].
-            ((char ~~ Character return) or:[str peekOrNil ~~ Character lf]) ifTrue:[
+            (withCEscapes and:[char == $\]) ifTrue:[
+                char := str nextOrNil ? char.
+                char == $r ifTrue:[
+                    char := Character return
+                ] ifFalse:[
+                    char == $n ifTrue:[
+                        char := Character linefeed
+                    ] ifFalse:[
+                        char == $b ifTrue:[
+                            char := Character backspace
+                        ] ifFalse:[
+                            char == $t ifTrue:[
+                                char := Character tab
+                            ]
+                        ]
+                    ]
+                ].
+            ].
+            keepCRs ifTrue:[
+                collected nextPut:char.
+            ] ifFalse:[
                 "compress CRLF to LF, but keep a single CR"
-                collected nextPut:char.
+                ((char ~~ Character return) or:[str peekOrNil ~~ Character lf]) ifTrue:[
+                    collected nextPut:char.
+                ]
             ].
         ].
         "if we come here, we reached the end without finding a closing $'"
@@ -289,14 +330,60 @@
     ^ exceptionBlock value
 
     "
-     String readFrom:('''hello world''' readStream)
-     String readFrom:('''hello '''' world''' readStream)
-     String readFrom:('1 ''hello'' ' readStream)
-     String readFrom:('1 ''hello'' ' readStream) onError:['foobar']
+     String readSmalltalkStringFrom:('''hello world''' readStream) onError:[self halt]
+     String readSmalltalkStringFrom:('''hello '''' world''' readStream) onError:[self halt]
+     String readSmalltalkStringFrom:('1 ''hello'' ' readStream) onError:[self halt]
+     String readSmalltalkStringFrom:('1 ''hello'' ' readStream) onError:['foobar']
+     String readSmalltalkStringFrom:('''hello\nworld''' readStream) onError:[self halt. 'foobar'] 
+
+     String readSmalltalkStringFrom:('''hello\nworld''' readStream) keepCRs:false onError:[self halt. 'foobar']   
+     String readSmalltalkStringFrom:('c''hello\nworld''' readStream) keepCRs:false onError:[self halt. 'foobar'] 
     "
 
     "Created: / 05-07-2006 / 16:41:04 / cg"
     "Modified: / 06-10-2006 / 14:05:32 / cg"
+    "Modified (comment): / 02-08-2019 / 10:10:46 / Stefan Vogel"
+!
+
+readSmalltalkStringFrom:aStreamOrString onError:exceptionBlock
+    "read & return the next String from the (character-)stream aStream;
+     skipping all whitespace first; return the value of exceptionBlock,
+     if no string can be read. The sequence of characters as read from the
+     stream must be one as stored via storeOn: or storeString."
+
+    ^ self readSmalltalkStringFrom:aStreamOrString keepCRs:false onError:exceptionBlock
+
+    "
+     String readSmalltalkStringFrom:('''hello world''' readStream) onError:[self halt]
+     String readSmalltalkStringFrom:('''hello '''' world''' readStream) onError:[self halt]
+     String readSmalltalkStringFrom:('1 ''hello'' ' readStream) onError:[self halt]
+     String readSmalltalkStringFrom:('1 ''hello'' ' readStream) onError:['foobar']
+    "
+
+    "Created: / 05-07-2006 / 16:41:04 / cg"
+    "Modified: / 06-10-2006 / 14:05:32 / cg"
+    "Modified (comment): / 02-08-2019 / 10:10:46 / Stefan Vogel"
+!
+
+readSmalltalkStringWithCRsFrom:aStreamOrString onError:exceptionBlock
+    "read & return the next String from the (character-)stream aStream;
+     skipping all whitespace first; return the value of exceptionBlock,
+     if no string can be read. The sequence of characters as read from the
+     stream must be one as stored via storeOn: or storeString.
+
+     Different from #readSmalltalStringFrom:onError: we keep CRLF as is."
+
+    ^ self readSmalltalkStringFrom:aStreamOrString keepCRs:true onError:exceptionBlock
+
+    "
+     String readSmalltalkStringWithCRsFrom:('''hello world''' readStream) onError:[self halt]  
+     String readSmalltalkStringWithCRsFrom:('''hello '''' world''' readStream) onError:[self halt]
+     String readSmalltalkStringWithCRsFrom:('1 ''hello'' ' readStream) onError:[self halt]
+     String readSmalltalkStringWithCRsFrom:('1 ''hello'' ' readStream) onError:['foobar']
+    "
+
+    "Created: / 01-08-2019 / 16:11:25 / Stefan Vogel"
+    "Modified: / 02-08-2019 / 10:11:06 / Stefan Vogel"
 !
 
 writeStreamClass
@@ -322,8 +409,6 @@
     "Created: / 09-01-2011 / 10:37:57 / cg"
 ! !
 
-
-
 !CharacterArray class methodsFor:'Compatibility-VW'!
 
 fromIntegerArray: anArray
@@ -350,23 +435,24 @@
      This may happen for example, if a non EUC coded 8-bit string
      is attempted to be decoded into a JIS string."
 
-    ^ DecodingFailedSignal
-
-    "Created: 28.6.1997 / 20:09:55 / cg"
-    "Modified: 3.8.1997 / 18:16:47 / cg"
+    ^ DecodingError
+
+    "Created: / 28-06-1997 / 20:09:55 / cg"
+    "Modified: / 03-08-1997 / 18:16:47 / cg"
+    "Modified: / 16-01-2018 / 18:58:10 / stefan"
 !
 
 encodingFailedSignal
     "return the (query-) signal, raised when encoding of a string is not possible
      due to invalid characters contained in the source."
 
-    ^ EncodingFailedSignal
-
-    "Modified: 28.6.1997 / 20:09:35 / cg"
-    "Created: 3.8.1997 / 18:16:40 / cg"
+    ^ EncodingError
+
+    "Modified: / 28-06-1997 / 20:09:35 / cg"
+    "Created: / 03-08-1997 / 18:16:40 / cg"
+    "Modified: / 16-01-2018 / 18:59:04 / stefan"
 ! !
 
-
 !CharacterArray class methodsFor:'cleanup'!
 
 lowSpaceCleanup
@@ -384,6 +470,26 @@
 
 !CharacterArray class methodsFor:'encoding & decoding'!
 
+deadKeyMap
+    "returns a 2-stage map from ch2 -> ch1 -> mappedChar
+     for deadkey processing (i.e. for making combining chars regular ones).
+     Caveat: 
+        possibly incomplete: only COMBINING_DIACRITICAL_MARKS are cared for.
+        Does not care for COMBINING_DIACRITICAL_MARKS_EXTENDED
+        and COMBINING_DIACRITICAL_MARKS_SUPPLEMENT.
+        However; those are used for German dialectology, ancient Greek and other similar
+        exotic uses. Probably noone will ever even notice that they are missing..."
+     
+    DeadKeyMap isNil ifTrue:[
+        self setupNormalizationMaps
+    ].
+    ^ DeadKeyMap
+
+    "
+     self deadKeyMap
+    "
+!
+
 decodeFromUTF8:aStringOrByteCollection
     "given a string in UTF8 encoding,
      return a new string containing the same characters, in Unicode encoding.
@@ -393,145 +499,136 @@
      (ST/X never uses utf8 internally, but always uses strings of fully decoded unicode characters).
      This only handles up-to 30bit characters."
 
-    |sz anyAbove7BitAscii nBitsRequired
-     ascii "{ Class: SmallInteger }"
+    |decodedSize nBitsRequired
+     codepoint "{ Class: SmallInteger }"
      byte  "{ Class: SmallInteger }"
-     lastIdx  "{ Class: SmallInteger }"
+     encodedSize  "{ Class: SmallInteger }"
      srcIdx  "{ Class: SmallInteger }"
      idx  "{ Class: SmallInteger }"
      nFollowBytes  "{ Class: SmallInteger }"
      minValue "{ Class: SmallInteger }"
      newString|
 
-    "/ fast track, also avoid creation of new strings if aStringOrByteCollection is already a 7-bit string
-    aStringOrByteCollection containsNon7BitAscii ifFalse:[
-        ^ aStringOrByteCollection asSingleByteString
+    encodedSize := aStringOrByteCollection size.
+    decodedSize := aStringOrByteCollection utf8DecodedSize.
+    
+    encodedSize == decodedSize ifTrue:[
+        "/ fast track, also avoid creation of new strings if aStringOrByteCollection is already a 7-bit string
+        ^ aStringOrByteCollection asSingleByteStringIfPossible
     ].
 
     nBitsRequired := 8.
-    anyAbove7BitAscii := false.
-    sz := 0.
-
-    lastIdx := aStringOrByteCollection size.
     srcIdx := 1.
 
-    "first determine the string size and max element size.
-     Check for UTF-8 confomance on the fly."
-    [srcIdx <= lastIdx] whileTrue:[
-        byte := ascii := aStringOrByteCollection byteAt:srcIdx. 
+    "this loop is only used to find the largest character"
+    [srcIdx <= encodedSize] whileTrue:[
+        byte := aStringOrByteCollection byteAt:srcIdx. 
         srcIdx := srcIdx + 1.
-        (byte bitAnd:16r80) ~~ 0 ifTrue:[
-            anyAbove7BitAscii := true.
+        byte > 16r7F ifTrue:[
             (byte bitAnd:2r11100000) == 2r11000000 ifTrue:[
                 "/ 80 .. 7FF
-                ascii := byte bitAnd:2r00011111.
-                nFollowBytes := 1.
-                minValue := 16r80.
+                nBitsRequired < 16 ifTrue:[
+                    codepoint := ((byte bitAnd:2r00011111) bitShift:6)
+                               + ((aStringOrByteCollection byteAt:srcIdx) bitAnd:2r00111111).
+                    codepoint > 16rFF ifTrue:[
+                        nBitsRequired := 16.
+                    ].
+                ].
+                srcIdx := srcIdx + 1.
             ] ifFalse:[(byte bitAnd:2r11110000) == 2r11100000 ifTrue:[
                 "/ 800 .. FFFF
-                ascii := byte bitAnd:2r00001111.
-                nFollowBytes := 2.
-                minValue := 16r800.
+                srcIdx := srcIdx + 2.
+                nBitsRequired < 16 ifTrue:[nBitsRequired := 16].
             ] ifFalse:[(byte bitAnd:2r11111000) == 2r11110000 ifTrue:[
                 "/ 10000 .. 1FFFFF
-                ascii := byte bitAnd:2r00000111.
-                nFollowBytes := 3.
-                minValue := 16r10000.
+                srcIdx := srcIdx + 3.
+                nBitsRequired := 32.
             ] ifFalse:[(byte bitAnd:2r11111100) == 2r11111000 ifTrue:[
+                "5 byte sequences do not result in valid unicode"
                 "/ 200000 .. 3FFFFFF
-                ascii := byte bitAnd:2r00000011.
-                nFollowBytes := 4.
-                minValue := 16r200000.
+                srcIdx := srcIdx + 4.
+                nBitsRequired := 32.
             ] ifFalse:[(byte bitAnd:2r11111110) == 2r11111100 ifTrue:[
+                "6 byte sequences do not result in valid unicode"
                 "/ 4000000 .. 7FFFFFFF
-                ascii := byte bitAnd:2r00000001.
-                ascii ~~ 0 ifTrue:[
-                    "/ ST/X can only represent 30 bit unicode characters.
+                (byte bitAnd:2r00000001) ~~ 0 ifTrue:[
+                    "/ ST/X can only represent up to 30 bit characters.
                     "/ but the max unicode character is defined as 16r10 FFFF anyway
                     ^ DecodingError newException
                            defaultValue:aStringOrByteCollection;
                            raiseRequestWith:aStringOrByteCollection 
                            errorString:('unicode character out of range at: %1' bindWith:srcIdx).
                 ].
-                nFollowBytes := 5.
-                minValue := 16r4000000.
+                srcIdx := srcIdx + 5.
+                nBitsRequired := 32.
             ] ifFalse:[
                 ^ DecodingError newException
                        defaultValue:aStringOrByteCollection;
                        raiseRequestWith:aStringOrByteCollection errorString:'invalid utf8 encoding'.
             ]]]]].
-
-            nFollowBytes timesRepeat:[
-                byte := aStringOrByteCollection byteAt:srcIdx.
-                srcIdx := srcIdx + 1.
-                (byte bitAnd:2r11000000) ~~ 2r10000000 ifTrue:[
-                    ^ DecodingError newException
-                           defaultValue:aStringOrByteCollection;
-                           raiseRequestWith:aStringOrByteCollection 
-                           errorString:('illegal followbyte: 0x%1 at:%2' bindWith:(byte hexPrintString:2) with:srcIdx-1).
-                ].
-                ascii := (ascii bitShift:6) bitOr:(byte bitAnd:2r00111111). 
-            ]. 
-            ascii > 16rFFFF ifTrue:[
-                nBitsRequired < 32 ifTrue:[nBitsRequired := 32].
-            ] ifFalse:[ascii > 16rFF ifTrue:[
-                nBitsRequired < 16 ifTrue:[nBitsRequired := 16].
-            ]].
-            ascii < minValue ifTrue:[
-                "encoding a value in a longer utf8-sequence than required is not allowed
-                 and imposes a security risk"
-                ^ DecodingError newException
-                       defaultValue:aStringOrByteCollection;
-                       raiseRequestWith:aStringOrByteCollection errorString:'overlong utf8 sequence'.
-            ].
         ].
-        sz := sz + 1.
     ].
 
     nBitsRequired == 8 ifTrue:[
-        anyAbove7BitAscii ifFalse:[
-            "/ can return the original string
-            ^ aStringOrByteCollection asSingleByteString.
-        ].
-        newString := String uninitializedNew:sz
-    ] ifFalse:[nBitsRequired <= 16 ifTrue:[
-        newString := Unicode16String new:sz
+        newString := String uninitializedNew:decodedSize
+    ] ifFalse:[nBitsRequired == 16 ifTrue:[
+        newString := Unicode16String new:decodedSize
     ] ifFalse:[
-        newString := Unicode32String new:sz
+        newString := Unicode32String new:decodedSize
     ]].
 
     idx := srcIdx := 1.
 
     "now fill the string"
-    [srcIdx <= lastIdx] whileTrue:[
-        byte := ascii := aStringOrByteCollection byteAt:srcIdx.
+    [srcIdx <= encodedSize] whileTrue:[
+        byte := codepoint := aStringOrByteCollection byteAt:srcIdx.
         srcIdx := srcIdx + 1.
-        (byte bitAnd:2r10000000) ~~ 0 ifTrue:[
+        byte > 16r7F ifTrue:[
             (byte bitAnd:2r11100000) == 2r11000000 ifTrue:[
-                ascii := byte bitAnd:2r00011111.
+                codepoint := byte bitAnd:2r00011111.
                 nFollowBytes := 1.
+                minValue := 16r80.
             ] ifFalse:[(byte bitAnd:2r11110000) == 2r11100000 ifTrue:[
-                ascii := byte bitAnd:2r00001111.
+                codepoint := byte bitAnd:2r00001111.
                 nFollowBytes := 2.
+                minValue := 16r800.
             ] ifFalse:[(byte bitAnd:2r11111000) == 2r11110000 ifTrue:[
-                ascii := byte bitAnd:2r00000111.
+                codepoint := byte bitAnd:2r00000111.
                 nFollowBytes := 3.
+                minValue := 16r10000.
             ] ifFalse:[(byte bitAnd:2r11111100) == 2r11111000 ifTrue:[
                 "5 byte sequences do not result in valid unicode"
-                ascii := byte bitAnd:2r00000011.
+                codepoint := byte bitAnd:2r00000011.
                 nFollowBytes := 4.
+                minValue := 16r200000.
             ] ifFalse:[(byte bitAnd:2r11111110) == 2r11111100 ifTrue:[
                 "6 byte sequences do not result in valid unicode"
-                ascii := byte bitAnd:2r00000001.
+                codepoint := byte bitAnd:2r00000001.
                 nFollowBytes := 5.
+                minValue := 16r4000000.
             ]]]]].
+
             nFollowBytes timesRepeat:[
                 byte := aStringOrByteCollection byteAt:srcIdx.
+                (byte bitAnd:2r11000000) ~~ 2r10000000 ifTrue:[
+                    ^ DecodingError newException
+                           defaultValue:aStringOrByteCollection;
+                           raiseRequestWith:aStringOrByteCollection 
+                           errorString:('illegal followbyte (expect 0x80): 0x%1 at:%2' bindWith:(byte hexPrintString:2) with:srcIdx).
+                ].
                 srcIdx := srcIdx + 1.
-                ascii := (ascii bitShift:6) bitOr:(byte bitAnd:2r00111111). 
+                codepoint := (codepoint bitShift:6) bitOr:(byte bitAnd:2r00111111). 
+            ].
+
+            codepoint < minValue ifTrue:[
+                "encoding a value in a longer utf8-sequence than required is not allowed
+                 and imposes a security risk. Proceed to continue with decoding."
+                DecodingError newException
+                       defaultValue:aStringOrByteCollection;
+                       raiseRequestWith:aStringOrByteCollection errorString:'overlong utf8 sequence'.
             ].
         ].
-        newString at:idx put:(Character value:ascii).
+        newString at:idx put:(Character value:codepoint).
         idx := idx + 1.
     ].
     ^ newString
@@ -539,10 +636,9 @@
     "
      CharacterArray decodeFromUTF8:#[ 16r41 16r42 ]
      CharacterArray decodeFromUTF8:#[ 16rC6 16r8F ]
-     CharacterArray decodeFromUTF8:#[ 16rE0 16r81 16r02 ]
      CharacterArray decodeFromUTF8:#[ 16rEF 16rBF 16rBF ]
 
-   rfc2279 (deprecated) examples:
+   rfc3629 examples:
      CharacterArray decodeFromUTF8:#[ 16r41 16rE2 16r89 16rA2 16rCE 16r91 16r2E ]
      CharacterArray decodeFromUTF8:#[ 16rED 16r95 16r9C 16rEA 16rB5 16rAD 16rEC 16r96 16rB4 ]
      CharacterArray decodeFromUTF8:#[ 16rE6 16r97 16rA5 16rE6 16r9C 16rAC 16rE8 16rAA 16r9E ]
@@ -550,28 +646,16 @@
    invalid:
      CharacterArray decodeFromUTF8:#[ 16rC0 16r80 ]
      CharacterArray decodeFromUTF8:#[ 16rE0 16r80 16r80 ]
-    "
-
-    "
-     CharacterArray decodeFromUTF8:#[ 16r41 16r42 ]
-     CharacterArray decodeFromUTF8:#[ 16rC1 16r02 ]
      CharacterArray decodeFromUTF8:#[ 16rE0 16r81 16r02 ]
-     CharacterArray decodeFromUTF8:#[ 16rEF 16rBF 16rBF ]
-
-   rfc2279 examples:
-     CharacterArray decodeFromUTF8:#[ 16r41 16rE2 16r89 16rA2 16rCE 16r91 16r2E ]
-     CharacterArray decodeFromUTF8:#[ 16rED 16r95 16r9C 16rEA 16rB5 16rAD 16rEC 16r96 16rB4 ]
-     CharacterArray decodeFromUTF8:#[ 16rE6 16r97 16rA5 16rE6 16r9C 16rAC 16rE8 16rAA 16r9E ]
-
-   invalid:
-     CharacterArray decodeFromUTF8:#[ 16rC0 16r80 ]
-     CharacterArray decodeFromUTF8:#[ 16rE0 16r80 16r80 ]
-    "
+    "
+
+    "Modified: / 07-02-2017 / 17:41:17 / stefan"
+    "Modified: / 04-10-2018 / 13:29:53 / Claus Gittinger"
 !
 
 setupNormalizationMaps
     "returns a 2-stage map from ch2 -> ch1 -> mappedChar.
-     for unicode normalization 
+     for unicode normalization and deadKey translation
      (i.e. for replacing combining char-sequences with regular characters).
      ch2 is the combining charCode (eg. 0x0308), ch1 is the previous character (eg. $A),
      mappedChar is the result (eg. $Ä).
@@ -586,25 +670,39 @@
 
     UnicodeNormalizationMap := Dictionary new.
     UnicodeDenormalizationMap := Dictionary new.
-
-    def := [:combiner :chars :mappedChars |
-               |d|
-
-               d := UnicodeNormalizationMap at:combiner ifAbsentPut:[Dictionary new].
-               chars with:mappedChars do:[:ch1 :mappedChar | 
-                    d at:ch1 put:mappedChar.
+    DeadKeyMap := Dictionary new.
+
+    def := 
+        [:combiner :deadKey :chars :mappedChars |
+            |dN dD|
+
+            combiner notNil ifTrue:[ 
+                dN := UnicodeNormalizationMap at:combiner ifAbsentPut:[Dictionary new].
+            ].
+            deadKey notNil ifTrue:[
+                dD := DeadKeyMap at:deadKey ifAbsentPut:[Dictionary new].
+            ].
+            chars with:mappedChars do:[:ch1 :mappedChar | 
+                dN notNil ifTrue:[ 
+                    dN at:ch1 put:mappedChar. 
                     UnicodeDenormalizationMap at:mappedChar put:(Unicode16String with:ch1 with:combiner).
-               ].
-           ].        
-    def value:(Character codePoint:16r0300) "grave"         value:'AEIOUaeiouWw' value:'ÀÈÌÒÙàèìòùẀẁ'.
-    def value:(Character codePoint:16r0301) "acute"         value:'AEIOUYaeiouyÇçKkMmPpWw' value:'ÁÉÍÓÚÝáéíóúýḈḉḰḱḾḿṔṕẂẃ'.
-    def value:(Character codePoint:16r0302) "circumflex"    value:'AEIOUaeiouZz' value:'ÂÊÎÔÛâêîôûẐẑ'.
-    def value:(Character codePoint:16r0303) "tilde"         value:'AONaon' value:'ÃÕÑãõñ'.
-    def value:(Character codePoint:16r0307) "dot over"      value:'BbDdFfHhMmNnPpRrSsTtWwXxYyṢṣ' value:'ḂḃḊḋḞḟḢḣṀṁṄṅṖṗṘṙṠṡṪṫẆẇẊẋẎẏṨṩ'.
-    def value:(Character codePoint:16r0308) "diaresis"      value:'AEIOUaeiouyHhWwXxt' value:'ÄËÏÖÜäëïöüÿḦḧẄẅẌẍẗ'.
-    def value:(Character codePoint:16r030A) "ring"          value:'Aawy' value:'Ååẘẙ'.
-    def value:(Character codePoint:16r0323) "dot under"     value:'AaBbDdEeIiHhKkLlMmNnOoRrSsTtUuVvWwZzṠṡ' value:'ẠạḄḅḌḍẸẹỊịḤḥḲḳḶḷṂṃṆṇỌọṚṛṢṣṬṭỤụṾṿẈẉẒẓṨṩ'.
-    def value:(Character codePoint:16r0327) "cedilla"       value:'Cc' value:'Çç'.
+                ].
+                dD notNil ifTrue:[ dD at:ch1 put:mappedChar ].
+           ].
+       ].
+
+    def value:(Character codePoint:16r0300) value:$`  "grave"         value:'AEIOUaeiouWw' value:'ÀÈÌÒÙàèìòùẀẁ'.
+    def value:(Character codePoint:16r0301) value:$'  "acute"         value:'AEIOUYaeiouyÇçKkMmPpWw' value:'ÁÉÍÓÚÝáéíóúýḈḉḰḱḾḿṔṕẂẃ'.
+    def value:(Character codePoint:16r0302) value:$^  "circumflex"    value:'AEIOUWaeiouZzw' value:'ÂÊÎÔÛŴâêîôûẐẑŵ'.
+    def value:(Character codePoint:16r0303) value:$~  "tilde"         value:'AONaon' value:'ÃÕÑãõñ'.
+    def value:(Character codePoint:16r0307) value:nil "dot over"      value:'BbDdFfHhMmNnPpRrSsTtWwXxYyṢṣ' value:'ḂḃḊḋḞḟḢḣṀṁṄṅṖṗṘṙṠṡṪṫẆẇẊẋẎẏṨṩ'.
+    def value:(Character codePoint:16r0308) value:nil "diaresis"      value:'AEIOUaeiouyHhWwXxt' value:'ÄËÏÖÜäëïöüÿḦḧẄẅẌẍẗ'.
+    def value:(Character codePoint:16r030A) value:$°  "ring"          value:'Aawy' value:'Ååẘẙ'.
+    def value:(Character codePoint:16r0323) value:nil "dot under"     value:'AaBbDdEeIiHhKkLlMmNnOoRrSsTtUuVvWwZzṠṡ' value:'ẠạḄḅḌḍẸẹỊịḤḥḲḳḶḷṂṃṆṇỌọṚṛṢṣṬṭỤụṾṿẈẉẒẓṨṩ'.
+    def value:(Character codePoint:16r0327) value:$,  "cedilla"       value:'Cc' value:'Çç'.
+
+    "/ def value:nil value:$" value:'AaEeIiOo' value:'ȀȁȄȅȈȉȌȍ'.
+    def value:nil value:$"  "diaresis"      value:'AEIOUaeiouyHhWwXxt' value:'ÄËÏÖÜäëïöüÿḦḧẄẅẌẍẗ'.
 
     "
      self setupNormalizationMaps
@@ -651,7 +749,6 @@
     "
 ! !
 
-
 !CharacterArray class methodsFor:'pattern matching'!
 
 matchEscapeCharacter
@@ -949,77 +1046,95 @@
     "Modified: 2.4.1997 / 16:20:29 / cg"
 !
 
-matchScanArrayFrom:aString escapeCharacter:escape
+matchScanArrayFrom:aString escapeCharacter:escape 
     "scan a pattern string and decompose it into a scanArray.
      This is processed faster (especially with character ranges), and
      can also be reused later. (if the same pattern is to be searched again)"
-
-    |coll
-     idx "{ Class: SmallInteger }"
-     end c1 c2 matchSet previous|
+    
+    |coll 
+     idx         "{ Class: SmallInteger }"
+     end c1 c2 matchSet previous escapeBlock |
 
     previous := nil.
-
     coll := OrderedCollection new.
-    idx := 1. end := aString size.
-    [idx <= end] whileTrue:[
+    idx := 1.
+    end := aString size.
+    escapeBlock := [:c | 
+        idx := idx + 1.
+        idx > end ifTrue:[
+            "/ mhmh - what should we do here ?
+            c
+        ] ifFalse:[
+            aString at:idx.
+        ]
+    ].
+    [ idx <= end ] whileTrue:[
         |char this|
 
         char := aString at:idx.
-        char == $* ifTrue:[
-            previous ~~ #anyString ifTrue:[
-                this := #anyString
-            ]
+        char == escape ifTrue:[
+            this:=escapeBlock value:char.
         ] ifFalse:[
-            char == $# ifTrue:[
+            char == $* ifTrue:[
                 previous ~~ #anyString ifTrue:[
-                    this := #any
+                    this := #anyString
                 ]
             ] 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
+                char == $# ifTrue:[
+                    previous ~~ #anyString ifTrue:[
+                        this := #any
+                    ]
                 ] ifFalse:[
-                    char == escape ifTrue:[
+                    char == $[ ifTrue:[
+                        matchSet := IdentitySet new.
                         idx := idx + 1.
                         idx > end ifTrue:[
-                            "/ mhmh - what should we do here ?
-                            this := char
-                        ] ifFalse:[
-                            this := aString at:idx.
-                        ]
+                            ^ nil
+                        ].
+                        char := aString at:idx.
+                        c1 := nil.
+                        [ char ~~ $] ] whileTrue:[
+                            char == escape ifTrue:[
+                                matchSet add:(escapeBlock value:char).
+                                idx := idx + 1
+                            ] ifFalse:[
+                                ((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 sort.
                     ] ifFalse:[
                         this := char
                     ]
                 ]
             ]
         ].
-        this notNil ifTrue:[coll add:this. previous := this].
+        this notNil ifTrue:[
+            coll add:this.
+            previous := this
+        ].
         idx := idx + 1
     ].
-
     ^ coll asArray
 
     "
@@ -1029,14 +1144,20 @@
      String matchScanArrayFrom:'\*uter'
      String matchScanArrayFrom:'[cC]#mpute[rR]'
      String matchScanArrayFrom:'[abcd]*'
+     String matchScanArrayFrom:'[abcdŴĂĂ]*'
      String matchScanArrayFrom:'[a-k]*'
      String matchScanArrayFrom:'*some*compl*ern*'
      String matchScanArrayFrom:'[a-'
      String matchScanArrayFrom:'[a-zA-Z]'
      String matchScanArrayFrom:'[a-z01234A-Z]'
-    "
-
-    "Modified: 2.4.1997 / 16:20:29 / cg"
+     String matchScanArrayFrom:'[A-Z$_][A-Za-z0-9$\[\]]*'
+     String matchScanArrayFrom:'[A-Z$\[\]]*'
+     String matchScanArrayFrom:'[A-Z$_\[][A-Za-z0-9$\-\] ]*'
+     ."
+
+    "Modified: / 02-04-1997 / 16:20:29 / cg"
+    "Modified: / 03-12-2018 / 15:41:54 / Stefan Vogel"
+    "Modified (comment): / 23-07-2020 / 10:04:58 / alkurz"
 ! !
 
 !CharacterArray class methodsFor:'queries'!
@@ -1146,7 +1267,6 @@
     "
 ! !
 
-
 !CharacterArray methodsFor:'Compatibility-ANSI'!
 
 addLineDelimiters
@@ -1157,7 +1277,6 @@
     "Modified: / 13.11.2001 / 19:16:25 / cg"
 ! !
 
-
 !CharacterArray methodsFor:'Compatibility-Dolphin'!
 
 copyExpanding:expandTable
@@ -1183,6 +1302,12 @@
         ].
     ].
     ^ ds contents.
+
+    "
+     'hello' copyExpanding:(Dictionary withKeys:{$h . $e . $o} andValues:{'HH' . 'EE' . $O })
+    "
+
+    "Modified (format): / 02-04-2019 / 10:59:59 / Claus Gittinger"
 !
 
 formatWith:aString
@@ -1222,7 +1347,7 @@
 
 % anArrayOfOperands
     "return a copy of the receiver, where a '%i' escape
-     is replaced by the coresponding string from the argument array.
+     is replaced by the corresponding string from the argument array.
      'i' may be between 1 and 9 (i.e. a maximum of 9 placeholders is allowed).
      Added for GNU-ST compatibility."
 
@@ -1235,9 +1360,10 @@
      'do you %(what) ?'
         % (Dictionary new at:#'what' put:'understand'; yourself)
     "
+
+    "Modified (comment): / 11-05-2017 / 12:43:08 / mawalch"
 ! !
 
-
 !CharacterArray methodsFor:'Compatibility-ST/V'!
 
 asArrayOfSubstrings
@@ -1258,25 +1384,6 @@
     "
 !
 
-byteAt:index put:aByte
-    "store a byte at given index.
-     This is an ST/V compatibility method."
-
-"/    (aByte == 0) ifTrue:[
-"/        "store a space instead"
-"/        ^ super basicAt:index put:(Character space)
-"/    ].
-    ^ self basicAt:index put:(Character value:aByte)
-
-    "
-     'hello' copy at:1 put:$H asciiValue; yourself
-     'hello' copy byteAt:1 put:72; yourself
-     'hello' copy byteAt:1 put:0; yourself
-    "
-
-    "Modified: 6.5.1996 / 10:35:26 / cg"
-!
-
 equalsIgnoreCase:aString
     "This is an ST/V compatibility method and an alias for sameAs:."
 
@@ -1372,7 +1479,11 @@
 asBoldText
     "return self as a bold text"
 
-    ^Text string: self emphasis: #bold
+    "this test allows for small non-gui apps to be built without libbasic2 (where Text is)"
+    Text isNil ifTrue:[^ self].
+    ^ Text string: self emphasis: #bold
+
+    "Modified (comment): / 20-06-2017 / 08:23:49 / cg"
 !
 
 asDate
@@ -1391,6 +1502,18 @@
     |len|
 
     ^ (len := self size) ~~ 0 and:[(self at:len) isDigit]
+    "
+     'hello' endsWithDigit
+     '12hello' endsWithDigit
+     'hello12' endsWithDigit
+    "
+    "
+     'hello' startsWithDigit
+     '12hello' startsWithDigit
+     'hello12' startsWithDigit
+    "
+
+    "Modified (comment): / 08-06-2019 / 17:23:38 / Claus Gittinger"
 !
 
 findDelimiters:delimiters startingAt:start
@@ -1449,35 +1572,30 @@
 includesSubString:aString caseSensitive:caseSensitive
     "sigh - an alias; added for Squeak/Pharo compatibility"
 
-    ^ self includesSubstring:aString caseSensitive:caseSensitive
+    ^ self includesString:aString caseSensitive:caseSensitive
 !
 
 includesSubstring: aString
     "sigh - an alias; added for Squeak/Pharo compatibility"
 
-    ^ self includesSubString: aString
+    ^ self includesString: aString
 
     "Created: / 03-10-2014 / 02:47:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-04-2019 / 12:32:50 / Stefan Vogel"
 !
 
 includesSubstring:aString caseSensitive:caseSensitive
     "return true, if a substring is contained in the receiver.
      The argument, caseSensitive controls if case is ignored in the compare."
 
-    "/ for now,  a q&d hack ...
-
-    caseSensitive ifFalse:[
-        ^ self asLowercase includesString:aString asLowercase
-    ].
-    ^ self includesString:aString
+    ^ (self indexOfSubCollection:aString startingAt:1 ifAbsent:0 caseSensitive:caseSensitive) ~~ 0
 
     "
      'hello world' includesSubstring:'Hel' caseSensitive:true
      'hello world' includesSubstring:'Hel' caseSensitive:false
     "
 
-
-
+    "Modified (comment): / 16-04-2019 / 12:35:33 / Stefan Vogel"
 !
 
 isAllDigits
@@ -1529,7 +1647,9 @@
      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 contains:[:delim | delim = (self at:i)]) ifFalse:[ 
+            ^ i 
+        ].
     ].
     ^ self size + 1
 
@@ -1539,6 +1659,8 @@
      '123***7890' skipDelimiters:'*' startingAt:10
      '123*******' skipDelimiters:'*' startingAt:10
     "
+
+    "Modified (format): / 11-06-2020 / 18:55:31 / Stefan Vogel"
 !
 
 substrings
@@ -1569,6 +1691,15 @@
     "
 !
 
+trimBoth
+    "return a copy of the receiver without leading and trailing whiteSpace.
+     Added for Squeak compatibility (an alias for withoutSeparators)"
+
+    ^ self withoutSeparators
+
+    "Created: / 03-07-2018 / 11:08:29 / Claus Gittinger"
+!
+
 truncateTo:smallSize
     "return myself or a copy shortened to smallSize.  1/18/96 sw"
 
@@ -1644,12 +1775,14 @@
      replaced by aString.
      This has been added for VisualAge compatibility."
 
-    ^ self expandPlaceholdersWith:(Array with:aString)
+    ^ self expandPlaceholdersWith:{ aString }
 
     "
      'do you like %1 ?' bindWith:'smalltalk'
      'do you like %(foo) ?' bindWithArguments:(Dictionary new at:'foo' put:'smalltalk'; yourself)
     "
+
+    "Modified (format): / 02-04-2019 / 14:05:22 / Claus Gittinger"
 !
 
 bindWith:string1 with:string2
@@ -1657,12 +1790,14 @@
      replaced by string1 and '%2' is replaced by string2.
      This has been added for VisualAge compatibility."
 
-    ^ self expandPlaceholdersWith:(Array with:string1 with:string2)
+    ^ self expandPlaceholdersWith:{string1 . string2}
 
     "
      'do you prefer %1 or rather %2 ?'
         bindWith:'smalltalk' with:'c++'
     "
+
+    "Modified (format): / 02-04-2019 / 14:05:32 / Claus Gittinger"
 !
 
 bindWith:str1 with:str2 with:str3
@@ -1670,12 +1805,14 @@
      are replaced by str1, str2 and str3 respectively.
      This has been added for VisualAge compatibility."
 
-    ^ self expandPlaceholdersWith:(Array with:str1 with:str2 with:str3)
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 }
 
     "
      'do you prefer %1 or rather %2 (not talking about %3) ?'
         bindWith:'smalltalk' with:'c++' with:'c'
     "
+
+    "Modified (format): / 02-04-2019 / 14:05:45 / Claus Gittinger"
 !
 
 bindWith:str1 with:str2 with:str3 with:str4
@@ -1683,12 +1820,14 @@
      are replaced by str1, str2, str3 and str4 respectively.
      This has been added for VisualAge compatibility."
 
-    ^ self expandPlaceholdersWith:(Array with:str1 with:str2 with:str3 with:str4)
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 }
 
     "
      'do you prefer %1 or rather %2 (not talking about %3 or even %4) ?'
         bindWith:'smalltalk' with:'c++' with:'c' with:'assembler'
     "
+
+    "Modified (format): / 02-04-2019 / 14:06:01 / Claus Gittinger"
 !
 
 bindWith:str1 with:str2 with:str3 with:str4 with:str5
@@ -1696,9 +1835,10 @@
      are replaced by str1 .. str5 respectively.
      This has been added for VisualAge compatibility."
 
-    ^ self expandPlaceholdersWith:(Array with:str1 with:str2 with:str3 with:str4 with:str5)
-
-    "Created: 31.1.1997 / 16:25:42 / cg"
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 }
+
+    "Created: / 31-01-1997 / 16:25:42 / cg"
+    "Modified: / 02-04-2019 / 14:06:17 / Claus Gittinger"
 !
 
 bindWith:str1 with:str2 with:str3 with:str4 with:str5 with:str6
@@ -1706,9 +1846,9 @@
      are replaced by str1 .. str6 respectively.
      This has been added for VisualAge compatibility."
 
-    ^ self expandPlaceholdersWith:(Array with:str1 with:str2
-                                         with:str3 with:str4
-                                         with:str5 with:str6)
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 . str6 }
+
+    "Modified (format): / 02-04-2019 / 14:06:36 / Claus Gittinger"
 !
 
 bindWith:str1 with:str2 with:str3 with:str4 with:str5 with:str6 with:str7
@@ -1716,10 +1856,9 @@
      are replaced by str1 .. str7 respectively.
      This has been added for VisualAge compatibility."
 
-    ^ self expandPlaceholdersWith:(Array with:str1 with:str2
-                                         with:str3 with:str4
-                                         with:str5 with:str6
-                                         with:str7)
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 . str6 . str7 }
+
+    "Modified (format): / 02-04-2019 / 14:06:59 / Claus Gittinger"
 !
 
 bindWith:str1 with:str2 with:str3 with:str4 with:str5 with:str6 with:str7 with:str8
@@ -1727,12 +1866,10 @@
      are replaced by str1 .. str8 respectively.
      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:str8)
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 . str6 . str7 . str8 }
 
     "Created: / 06-02-2012 / 10:33:18 / cg"
+    "Modified: / 02-04-2019 / 14:07:15 / Claus Gittinger"
 !
 
 bindWith:str1 with:str2 with:str3 with:str4 with:str5 with:str6 with:str7 with:str8 with:str9
@@ -1740,24 +1877,22 @@
      are replaced by str1 .. str9 respectively.
      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:str8
-                                         with:str9)
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 . str6 . str7 . str8 . str9 }
 
     "Created: / 14-02-2012 / 17:42:31 / cg"
-!
-
-bindWithArguments:anArrayOfStrings
+    "Modified: / 02-04-2019 / 14:07:35 / Claus Gittinger"
+!
+
+bindWithArguments:argumentsCollection
     "return a copy of the receiver, where a '%i' escape
-     is replaced by the coresponding string from the argument array.
-     'i' may be between 1 and 9 (i.e. a maximum of 9 placeholders is allowed).
+     is replaced by the corresponding string from the argument array.
+     'i' may be between 1 and 9 (i.e. a maximum of 9 placeholders is allowed)
+     or %(key); the argumentsCollection must then be a dictionary.
      To get an integer-indexed placeHolder followed by another digit,
      or an index > 9, you must use %(digit).
      This has been added for VisualAge compatibility."
 
-    ^ self expandPlaceholdersWith:anArrayOfStrings
+    ^ self expandPlaceholdersWith:argumentsCollection
 
     "
      'do you prefer %1 or rather %2 (not talking about %3) ?'
@@ -1766,6 +1901,8 @@
      'do you %(what) ?'
         bindWithArguments:(Dictionary new at:#'what' put:'understand'; yourself)
     "
+
+    "Modified (comment): / 11-05-2017 / 12:42:57 / mawalch"
 !
 
 subStrings
@@ -1804,6 +1941,139 @@
      Added for VisualAge compatibility (an alias for withoutSeparators)"
 
     ^ self withoutSeparators
+!
+
+with:aString
+    "return a copy of the receiver, where a '%1' escape is replaced by aString.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{ aString }
+
+    "
+     'do you like %1 ?' with:'smalltalk'
+     'do you like %(foo) ?' withArguments:(Dictionary new at:'foo' put:'smalltalk'; yourself)
+    "
+
+
+!
+
+with:string1 with:string2
+    "return a copy of the receiver, 
+     where a '%1' escape is replaced by string1 and '%2' is replaced by string2.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{string1 . string2}
+
+    "
+     'do you prefer %1 or rather %2 ?' with:'smalltalk' with:'c++'
+    "
+
+    "Modified (format): / 02-04-2019 / 14:05:32 / Claus Gittinger"
+!
+
+with:str1 with:str2 with:str3
+    "return a copy of the receiver, 
+     where a '%1', '%2' and '%3' escapes are replaced by str1, str2 and str3 respectively.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 }
+
+    "
+     'do you prefer %1 or rather %2 (not talking about %3) ?'
+        with:'smalltalk' with:'c++' with:'c'
+    "
+
+    "Modified (format): / 02-04-2019 / 14:05:45 / Claus Gittinger"
+!
+
+with:str1 with:str2 with:str3 with:str4
+    "return a copy of the receiver, where a '%1', '%2', '%3' and '%4' escapes
+     are replaced by str1, str2, str3 and str4 respectively.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 }
+
+    "
+     'do you prefer %1 or rather %2 (not talking about %3 or even %4) ?'
+        with:'smalltalk' with:'c++' with:'c' with:'assembler'
+    "
+
+    "Modified (format): / 02-04-2019 / 14:06:01 / Claus Gittinger"
+!
+
+with:str1 with:str2 with:str3 with:str4 with:str5
+    "return a copy of the receiver, where a '%1' .. '%5' escapes
+     are replaced by str1 .. str5 respectively.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 }
+
+    "Created: / 31-01-1997 / 16:25:42 / cg"
+    "Modified: / 02-04-2019 / 14:06:17 / Claus Gittinger"
+!
+
+with:str1 with:str2 with:str3 with:str4 with:str5 with:str6
+    "return a copy of the receiver, where a '%1' .. '%6' escapes
+     are replaced by str1 .. str6 respectively.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 . str6 }
+
+    "Modified (format): / 02-04-2019 / 14:06:36 / Claus Gittinger"
+!
+
+with:str1 with:str2 with:str3 with:str4 with:str5 with:str6 with:str7
+    "return a copy of the receiver, where a '%1' .. '%7' escapes
+     are replaced by str1 .. str7 respectively.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 . str6 . str7 }
+
+    "Modified (format): / 02-04-2019 / 14:06:59 / Claus Gittinger"
+!
+
+with:str1 with:str2 with:str3 with:str4 with:str5 with:str6 with:str7 with:str8
+    "return a copy of the receiver, where a '%1' .. '%8' escapes
+     are replaced by str1 .. str8 respectively.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 . str6 . str7 . str8 }
+
+    "Created: / 06-02-2012 / 10:33:18 / cg"
+    "Modified: / 02-04-2019 / 14:07:15 / Claus Gittinger"
+!
+
+with:str1 with:str2 with:str3 with:str4 with:str5 with:str6 with:str7 with:str8 with:str9
+    "return a copy of the receiver, where a '%1' .. '%9' escapes
+     are replaced by str1 .. str9 respectively.
+     Added for protocol compatibility with resourcePack xlation."
+
+    ^ self expandPlaceholdersWith:{ str1 . str2 . str3 . str4 . str5 . str6 . str7 . str8 . str9 }
+
+    "Created: / 14-02-2012 / 17:42:31 / cg"
+    "Modified: / 02-04-2019 / 14:07:35 / Claus Gittinger"
+!
+
+withArguments:argumentsCollection
+    "return a copy of the receiver, where the '%i' escapes
+     are replaced by the corresponding string from the argument array.
+     'i' may be between 1 and 9 (i.e. a maximum of 9 placeholders is allowed)
+     or %(key); the argumentsCollection must then be a dictionary.
+     To get an integer-indexed placeHolder followed by another digit,
+     or an index > 9, you must use %(digit).
+     This has been added for VisualAge compatibility."
+
+    ^ self expandPlaceholdersWith:argumentsCollection
+
+    "
+     'do you prefer %1 or rather %2 (not talking about %3) ?'
+        withArguments:#('smalltalk' 'c++' 'c')
+
+     'do you %(what) ?'
+        withArguments:(Dictionary new at:#'what' put:'understand'; yourself)
+    "
+
+    "Modified (comment): / 11-05-2017 / 12:42:57 / mawalch"
 ! !
 
 !CharacterArray methodsFor:'Compatibility-VW'!
@@ -1829,10 +2099,10 @@
      Read the comment in #expandMacrosWithArguments: about
      limited compatibility issues."
 
-    ^ self expandMacrosWithArguments:(Array with:arg)
-
-    "Created: / 1.11.1997 / 13:01:28 / cg"
-    "Modified: / 1.11.1997 / 13:30:50 / cg"
+    ^ self expandMacrosWithArguments:{ arg }
+
+    "Created: / 01-11-1997 / 13:01:28 / cg"
+    "Modified: / 02-04-2019 / 14:09:26 / Claus Gittinger"
 !
 
 expandMacrosWith:arg1 with:arg2
@@ -1841,9 +2111,10 @@
      Read the comment in #expandMacrosWithArguments: about
      limited compatibility issues."
 
-    ^ self expandMacrosWithArguments:(Array with:arg1 with:arg2)
-
-    "Modified: / 6.7.1998 / 21:58:14 / cg"
+    ^ self expandMacrosWithArguments:{arg1 . arg2 }
+
+    "Modified: / 06-07-1998 / 21:58:14 / cg"
+    "Modified: / 02-04-2019 / 14:09:36 / Claus Gittinger"
 !
 
 expandMacrosWith:arg1 with:arg2 with:arg3
@@ -1852,7 +2123,9 @@
      Read the comment in #expandMacrosWithArguments: about
      limited compatibility issues."
 
-    ^ self expandMacrosWithArguments:(Array with:arg1 with:arg2 with:arg3)
+    ^ self expandMacrosWithArguments:{ arg1 . arg2 . arg3 }
+
+    "Modified (format): / 02-04-2019 / 14:09:48 / Claus Gittinger"
 !
 
 expandMacrosWith:arg1 with:arg2 with:arg3 with:arg4
@@ -1861,7 +2134,9 @@
      Read the comment in #expandMacrosWithArguments: about
      limited compatibility issues."
 
-    ^ self expandMacrosWithArguments:(Array with:arg1 with:arg2 with:arg3 with:arg4)
+    ^ self expandMacrosWithArguments:{ arg1 . arg2 . arg3 . arg4 }
+
+    "Modified (format): / 02-04-2019 / 14:10:05 / Claus Gittinger"
 !
 
 expandMacrosWithArguments:argArray
@@ -1919,11 +2194,11 @@
                     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 proceedableError:'invalid format'.
                         ^ self
                     ].
                     fmt := in next.
-                    (fmt ~~ $? and:[in peek ~~ $>]) ifTrue:[
+                    (fmt ~~ $? and:[fmt ~~ $# and:[in peek ~~ $>]]) ifTrue:[
                         out nextPut:$<.
                         nr printOn:out.
                         out nextPut:fmt.
@@ -1947,10 +2222,11 @@
                             ] ifFalse:[
                                 out nextPutAll:arg asString string.  "see method comment: arg must know #asString"
                             ]
-                        ] ifFalse:[fmt == $? ifTrue:[
+                        ] ifFalse:[(fmt == $? or:[fmt == $#]) ifTrue:[
                             s1 := in upTo:$:.
                             s2 := in nextUpTo:$>.
-                            arg == true ifTrue:[
+                            ((fmt == $? and:[arg == true])
+                            or:[(fmt == $# and:[arg == 1])]) ifTrue:[
                                 out nextPutAll:s1
                             ] ifFalse:[
                                 out nextPutAll:s2
@@ -1982,6 +2258,7 @@
     "
 
     "Modified: / 18-09-2007 / 22:50:43 / cg"
+    "Modified: / 24-05-2018 / 21:06:31 / Claus Gittinger"
 !
 
 isCharacters
@@ -1995,25 +2272,24 @@
 !CharacterArray methodsFor:'JavaScript support'!
 
 unquote
-    "removes double quotes from the receiver.
+    "removes double quotes at begin and end from the receiver (but only if matching).
      This is the JavaScript standard unquote function."
 
     ^ self unquote:$"
 
     "
      'hello' quote unquote
-
-     JavaScriptParser evaluate:'''hello''.quote.unquote'
+     JavaScriptParser evaluate:'''hello''.quote().unquote()'
     "
 !
 
 unquote:quoteCharacter
-    "removes quoteCharacter from either end of the receiver."
+    "removes quoteCharacter (if present and matching) from either end of the receiver."
 
     |mySize|
 
     (mySize := self size) >= 2 ifTrue:[
-        ((self first == quoteCharacter) and:[self last == quoteCharacter]) ifTrue:[
+        (((self at:1) == quoteCharacter) and:[(self at:mySize) == quoteCharacter]) ifTrue:[
             ^ self copyFrom:2 to:mySize-1
         ].
     ].
@@ -2024,7 +2300,6 @@
     "
 ! !
 
-
 !CharacterArray methodsFor:'character searching'!
 
 includesMatchCharacters
@@ -2359,6 +2634,7 @@
 !
 
 after:aString
+    <resource: #obsolete>
     "Compare the receiver with the argument and return true if the
      receiver should come after the argument in a sorted list.
      Otherwise return false.
@@ -2368,9 +2644,55 @@
             Currently it is for Strings, but not for UnicodeStrings...
 
      STUPID:
-        #after has a completely different meaning in SeqColl ..."
+        #after has a completely different meaning in SeqColl...
+        ... therefore it is marked as obsolete.    
+    "
 
     ^ (self compareCollatingWith:aString) > 0
+
+    "Modified (comment): / 29-06-2018 / 11:41:33 / Claus Gittinger"
+!
+
+caselessAfter:aString
+    "True if the receiver comes after aString, if compared caseless.
+     (i.e. if receiver > aString, ignoring case)"
+
+    ^ (self compareCaselessWith:aString) > 0
+
+    "
+     'aaa1' > 'aaA2' -> true
+     'aaa1' caselessAfter: 'aaA2' -> false
+    "
+
+    "Created: / 29-05-2019 / 10:09:55 / Claus Gittinger"
+!
+
+caselessBefore:aString
+    "True if the receiver comes before aString, if compared caseless.
+     (i.e. if receiver < aString, ignoring case)"
+
+    ^ (self compareCaselessWith:aString) < 0
+
+    "
+     'aaa1' < 'aaA2' -> false
+     'aaa1' caselessBefore: 'aaA2' -> true
+    "
+
+    "Created: / 29-05-2019 / 10:09:18 / Claus Gittinger"
+!
+
+caselessEqual:aString
+    "True if the receiver has the same characters as aString, if compared caseless.
+     (i.e. if receiver = aString, ignoring case)"
+
+    ^ (self sameAs:aString)
+
+    "
+     'aaa1' = 'aaA1' -> false
+     'aaa1' caselessEqual: 'aaA1' -> true
+    "
+
+    "Created: / 29-05-2019 / 10:10:53 / Claus Gittinger"
 !
 
 compareAsVersionNumberWith:aStringOrCollection
@@ -2378,42 +2700,15 @@
      greater, 0 if equal and -1 if less than the argument in a sorted list.
      Compare as version numbers in the form a.b.c... ."
 
-    |rev1 rev2 removeTrailingZerosBlock trailingZerosCount|
-
-    rev1 := self asCollectionOfSubstringsSeparatedBy:$..
-    aStringOrCollection isString ifTrue:[
-        rev2 := aStringOrCollection asCollectionOfSubstringsSeparatedBy:$..
-    ].
-    rev1 := rev1 collect:[:each| each asInteger].
-    rev2 := rev2 collect:[:each| each asInteger].
-
-    removeTrailingZerosBlock := 
-        [:numbers |
-            trailingZerosCount := 0.
-            numbers reversed doWithExit:[:each :exit |
-                each == 0 ifTrue:[
-                    trailingZerosCount := trailingZerosCount + 1.
-                ] ifFalse:[
-                    exit value:nil.
-                ].
-            ].
-
-            trailingZerosCount > 0 ifTrue:[
-                numbers copyTo:numbers size - trailingZerosCount
-            ] ifFalse:[
-                numbers
-            ]
-        ].
-
-    rev1 := removeTrailingZerosBlock value:rev1.
-    rev2 := removeTrailingZerosBlock value:rev2.
-
-    ^ rev1 compareWith:rev2
+
+    ^ self asVersionNumberCollection 
+            compareWith:aStringOrCollection asVersionNumberCollection
 
    "
      self assert:('1' compareAsVersionNumberWith:'2') < 0.
      self assert:('2' compareAsVersionNumberWith:'1') > 0.
      self assert:('1.1' compareAsVersionNumberWith:'2.1.2') < 0.
+     self assert:('1.1a' compareAsVersionNumberWith:'2.1.2') < 0.
      self assert:('2.1' compareAsVersionNumberWith:'1.2.3') > 0.
      self assert:('1' compareAsVersionNumberWith:'1.1') < 0.
      self assert:('1.1' compareAsVersionNumberWith:'1') > 0.
@@ -2425,11 +2720,18 @@
      self assert:('1.2.3.4' compareAsVersionNumberWith:'1.2.3.4') = 0.
      self assert:('1.2.3.4' compareAsVersionNumberWith:'01.002.03.004') = 0.
      self assert:('1.2.3.4' compareAsVersionNumberWith:#(1 2 3 4)) = 0.
-    "
+     self assert:('1.2.3.4' compareAsVersionNumberWith:#('1' 2 3 4)) = 0.
+
+     self assert:('1.1' compareAsVersionNumberWith:'1.1a') < 0.
+
+    "
+
+    "Modified: / 25-10-2017 / 11:25:08 / stefan"
+    "Modified (format): / 20-06-2018 / 19:23:18 / Stefan Vogel"
 !
 
 compareCaselessWith:aString
-    "Compare the receiver against the argument, ignoreing case.
+    "Compare the receiver against the argument, ignoring case.
      Return 1 if the receiver is greater, 0 if equal and -1 if less than the argument.
 
      This comparison is based on the elements ascii code -
@@ -2455,7 +2757,14 @@
     mySize < otherSize ifTrue:[^ -1].
     ^ 0
 
-    "Modified: 22.4.1996 / 15:56:07 / cg"
+    "
+     'aaa1' < 'aaA2' -> false
+     'aaa1' compareCaselessWith: 'aaA2' -> -1
+    "
+
+    "Modified: / 22-04-1996 / 15:56:07 / cg"
+    "Modified (comment): / 26-10-2017 / 16:01:01 / mawalch"
+    "Modified (comment): / 29-05-2019 / 10:06:00 / Claus Gittinger"
 !
 
 compareCollatingWith:aString
@@ -2499,21 +2808,56 @@
     |s|
 
     (s := self string) ~~ self ifTrue:[
+        "/ here, if I am Text 
         ^ s endsWith:aStringOrCharacter
     ].
-    (self size ~~ 0 and:[aStringOrCharacter isCharacter]) ifTrue:[
+
+    (self size == 0) ifTrue:[^ false].
+    aStringOrCharacter isCharacter ifTrue:[
         ^ self last = aStringOrCharacter
     ].
     ^ super endsWith:aStringOrCharacter
 
     "
      'hello world' endsWith:'world'
+     'hello world' endsWith:$d
      'hello world' asText allBold endsWith:'world'
+     'hello world' asText allBold endsWith:$d
      'hello world' endsWith:''
      'hello world' asText allBold endsWith:''
-    "
-
-    "Modified: 12.5.1996 / 15:49:18 / cg"
+     'hello' endsWith:'hello'
+     '' endsWith:'hello'
+     '' endsWith:$a
+     '' endsWith:1234
+     'a' endsWith:1234 
+    "
+
+    "Modified: / 12-05-1996 / 15:49:18 / cg"
+    "Modified (comment): / 31-03-2020 / 11:19:30 / Stefan Vogel"
+!
+
+endsWith:aStringOrCharacter caseSensitive:caseSensitive
+    "return true, if the receiver ends with something, aStringOrCharacter.
+     If aStringOrCharacter is empty, true is returned"
+
+    |s|
+
+    caseSensitive ifTrue:[^ self endsWith:aStringOrCharacter].
+
+    (s := self string) ~~ self ifTrue:[
+        ^ s endsWith:aStringOrCharacter
+    ].
+    (self size ~~ 0 and:[aStringOrCharacter isCharacter]) ifTrue:[
+        ^ self last asLowercase = aStringOrCharacter asLowercase
+    ].
+    ^ self endsWith:aStringOrCharacter using:[:a :b | a asLowercase = b asLowercase].
+
+    "
+     'hello World' endsWith:'world' caseSensitive:true
+     'hello World' endsWith:'world' caseSensitive:false
+    "
+
+    "Created: / 29-06-2018 / 11:38:57 / Claus Gittinger"
 !
 
 hammingDistanceTo:aString
@@ -2523,12 +2867,18 @@
      Put another way, it measures the minimum number of substitutions required to change
      one into the other, or the number of errors that transformed one string into the other."
 
-    self assert:(aString size == self size).
-    ^ 1 to:self size count:[:idx | (self at:idx) ~= (aString at:idx)]
+    |mySize|
+
+    mySize := self size.
+    self assert:(aString size == mySize).
+    ^ 1 to:mySize count:[:idx | (self at:idx) ~= (aString at:idx)]
 
     "
      'roses' hammingDistanceTo:'toned'
-    "
+     'roses' hammingDistanceTo:'doses'
+    "
+
+    "Modified (comment): / 24-11-2017 / 08:50:58 / cg"
 !
 
 hash
@@ -2640,6 +2990,8 @@
     "return an integer useful as a hash-key.
      This method uses the fnv-1a algorithm
      (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)"
 
@@ -2648,6 +3000,10 @@
     h := 2166136261.
     self do:[:eachChar |
         byte := eachChar codePoint.
+        byte == 0 ifTrue:[
+            "/ stop
+            ^ (h bitXor: (h >> 30)) bitAnd: 16r3FFFFFFF.
+        ].
         h := h bitXor:byte.
         h := (h * 16777619) bitAnd:16rFFFFFFFF.
     ].
@@ -2668,8 +3024,40 @@
      'blablaHelloWorld' asUnicode16String hash_fnv1a
      'blablaHelloWorld' asUnicode32String hash_fnv1a
     "
-
-    "Modified: / 23-06-2016 / 23:15:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+hash_fnv1a_64
+    "return a 64bit integer useful as a hash-key.
+     This method uses the fnv-1a algorithm
+     (which is actually a very good one)."
+
+    |h byte|
+
+    h := 14695981039346656037.
+    self do:[:eachChar |
+        byte := eachChar codePoint.
+        h := h bitXor:byte.
+        h := (h * 1099511628211) bitAnd:16rFFFFFFFFFFFFFFFF.
+    ].
+    "/ make sure, it fits into 64 bit
+    h := (h bitXor: (h >> 30)) bitAnd: 16r3FFFFFFFFFFFFFFF.
+    ^ h
+
+    "
+     'abc' hash_fnv1a_64 
+     'abc' asUnicode16String hash_fnv1a_64
+     'abc' asUnicode32String hash_fnv1a_64
+
+     'foofooHelloWorld' hash_fnv1a_64
+     'foofooHelloWorld' asUnicode16String hash_fnv1a_64
+     'foofooHelloWorld' asUnicode32String hash_fnv1a_64
+
+     'blablaHelloWorld' hash_fnv1a_64
+     'blablaHelloWorld' asUnicode16String hash_fnv1a_64
+     'blablaHelloWorld' asUnicode32String hash_fnv1a_64
+    "
+
+    "Created: / 11-03-2019 / 11:47:15 / Claus Gittinger"
 !
 
 hash_java
@@ -2768,7 +3156,7 @@
      See IEEE transactions on Computers 1976 Pg 172 ff."
 
     "
-     in the following, we assume that ommiting a character
+     in the following, we assume that omiting a character
      is less of an error than inserting an extra character.
      Therefore the different insertion (i) and deletion (d) values.
         s: substitution weight (4)
@@ -2777,6 +3165,11 @@
         e: exchange weight (8)                       - or nil (then use s*2)
         i: insertion of extra character weight (2)
         d: delete of a character weight (6)
+
+     Notice that the standard levenshtein uses the same weight for insertion and deletion,
+     and is computed by:
+        'flaw' levenshteinTo:'lawn' s:2 k:nil c:nil i:1 d:1
+
     "
 
     ^ StringUtilities
@@ -2806,6 +3199,9 @@
 
      'comptuer' levenshteinTo:'computer'
     "
+
+    "Modified (comment): / 17-05-2017 / 16:15:41 / mawalch"
+    "Modified (comment): / 02-08-2017 / 17:13:04 / cg"
 !
 
 levenshteinTo:aString s:substWeight k:kbdTypoWeight c:caseWeight i:insrtWeight d:deleteWeight
@@ -3004,12 +3400,10 @@
             (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.
+                (i1 < size1 and: [(self at:next1) == (aString at:i2)]) ifFalse: [
                     i2 := next2
-                ]
+                ].
+                i1 := next1.
             ]
         ]
     ].
@@ -3024,6 +3418,8 @@
      'Smalltalk' spellAgainst: 'smalltlk'
      'Smalltalk' spellAgainst: 'Smalltolk'
     "
+
+    "Modified: / 11-06-2020 / 19:06:38 / Stefan Vogel"
 !
 
 startsWith:aStringOrCharacter
@@ -3035,7 +3431,7 @@
     |s|
 
     aStringOrCharacter isCharacter ifTrue:[
-        ^ (self size ~~ 0) and:[ (self at:1) == aStringOrCharacter ]
+        ^ (self size ~~ 0) and:[(self at:1) = aStringOrCharacter]
     ].
     (s := self string) ~~ self ifTrue:[
         ^ s startsWith:aStringOrCharacter
@@ -3052,8 +3448,73 @@
      'hello world' asText allBold startsWith:''
     "
 
-    "Created: 12.5.1996 / 15:46:40 / cg"
-    "Modified: 12.5.1996 / 15:49:24 / cg"
+    "Created: / 12-05-1996 / 15:46:40 / cg"
+    "Modified: / 29-06-2018 / 11:27:08 / Claus Gittinger"
+    "Modified (format): / 26-11-2018 / 14:15:31 / Stefan Vogel"
+!
+
+startsWith:aStringOrCharacter caseSensitive:caseSensitive
+    "return true, if the receiver starts with something, aStringOrCharacter.
+     If the argument is empty, true is returned.
+     Notice, that this is similar to, but slightly different from VW's and Squeak's beginsWith:,
+     which are both inconsistent w.r.t. an empty argument."
+
+    |s|
+
+    caseSensitive ifTrue:[
+        ^ self startsWith:aStringOrCharacter
+    ].
+    aStringOrCharacter isCharacter ifTrue:[
+        self size == 0 ifTrue:[
+            ^ false.
+        ].
+        s := self at:1.
+        ^ s == aStringOrCharacter or:[s asLowercase = aStringOrCharacter asLowercase]
+    ].
+    (s := self string) ~~ self ifTrue:[
+        ^ s startsWith:aStringOrCharacter caseSensitive:caseSensitive
+    ].
+    ^ self startsWith:aStringOrCharacter using:[:a :b | a asLowercase = b asLowercase].
+
+    "
+     'aBCde' startsWith:'abc' caseSensitive:true
+     'aBCde' startsWith:'abc' caseSensitive:false
+    "
+
+    "Created: / 29-06-2018 / 11:27:04 / Claus Gittinger"
+    "Modified: / 26-11-2018 / 14:18:43 / Stefan Vogel"
+!
+
+startsWithDigit
+    "Answer whether the receiver's first character represents a digit.  3/11/96 sw"
+
+    ^ self size ~~ 0 and:[(self at:1) isDigit]
+
+    "
+     'hello' startsWithDigit
+     '12hello' startsWithDigit
+     'hello12' startsWithDigit
+    "
+    "
+     'hello' endsWithDigit
+     '12hello' endsWithDigit
+     'hello12' endsWithDigit
+    "
+
+    "Created: / 08-06-2019 / 17:22:13 / Claus Gittinger"
+    "Modified: / 11-06-2020 / 19:04:00 / Stefan Vogel"
+!
+
+startsWithSeparator
+    "Answer whether the receiver's first character is whitespace"
+
+    ^ self size ~~ 0 and:[(self at:1) isSeparator]
+
+    "
+     'hello' startsWithSeparator 
+     ' 12hello' startsWithSeparator    
+     (Character tab,'hello12') startsWithSeparator  
+    "
 ! !
 
 !CharacterArray methodsFor:'converting'!
@@ -3080,7 +3541,7 @@
      The size of the returned byteArray will be the strings size multiplied by the
      size required for the largest character.
      Attention: The bytes are in native byte order.
-     Caveat: better use utf8Encoded, to get reproducable results"
+     Caveat: better use utf8Encoded, to get reproducible results"
 
     |bytes sz bytesPerCharacter idx str|
 
@@ -3113,6 +3574,7 @@
     ^ bytes
 
     "Created: / 27-07-2011 / 00:56:17 / cg"
+    "Modified (comment): / 11-05-2017 / 09:21:57 / mawalch"
 !
 
 asByteArrayMSB:msb
@@ -3120,7 +3582,7 @@
      return a byteArray containing single-, double- or even 4-bytewise values.
      The size of the returned byteArray will be the strings size multiplied by the
      size required for the largest character.
-     Caveat: better use utf8Encoded, to get reproducable results"
+     Caveat: better use utf8Encoded, to get reproducible results"
 
     |ba|
 
@@ -3129,6 +3591,8 @@
         ba swapBytes
     ].
     ^ ba
+
+    "Modified (comment): / 11-05-2017 / 09:22:01 / mawalch"
 !
 
 asCanonicalizedFilename
@@ -3161,9 +3625,8 @@
 !
 
 asCollectionOfLines
-    "return a collection containing the lines (separated by cr)
-     of the receiver. If multiple cr's occur in a row, the result will
-     contain empty strings.
+    "return a collection containing the lines (separated by cr) of the receiver. 
+     If multiple cr's occur in a row, the result will contain empty strings.
      If the string ends with a cr, an empty line will be found as last element of the resulting collection.
      See also #asCollectionOfLinesWithReturn
      (would have rather changed this method instead of adding another one, but a lot of code already uses
@@ -3178,12 +3641,57 @@
      ('foo \r\nbar\nbaz\t\r\n\r\nbla' printf:#())
         asCollectionOfLines collect:[:l | (l endsWith:Character return) ifTrue:[l copyButLast:1] ifFalse:l]
     "
+
+    "Modified (comment): / 03-07-2018 / 10:59:36 / Claus Gittinger"
+!
+
+asCollectionOfLinesDo:aBlock
+    "evaluate aBlock for each line (separated by cr) of the receiver.
+     Returns the number of lines (i.e. the number of invocations of aBlock).
+     This is similar to 'asCollectionOfLines do:...' or 'asStringCollection do:...'
+     but avoids the creation of a temporary collection."
+
+    |count  "{ Class:SmallInteger }"
+     start  "{ Class:SmallInteger }"
+     stop   "{ Class:SmallInteger }"
+     mySize "{ Class:SmallInteger }"|
+
+    count := 0.
+    start := 1.
+    mySize := self size.
+    [start <= mySize] whileTrue:[
+        stop := self indexOf:Character cr startingAt:start.
+        stop == 0 ifTrue:[
+            aBlock value:(self copyFrom:start to:mySize).
+            ^ count + 1
+        ].
+        aBlock value:(self copyFrom:start to:(stop - 1)).
+        start := stop+1.
+        count := count + 1
+    ].
+    ^ count
+
+    "
+
+     c'hello\nworld\nisnt\nthis\n\nnice' asCollectionOfLinesDo:[:l | Transcript showCR:l]
+     c'hello\nworld\nisnt\nthis\n\nnice' asStringCollection do:[:l | Transcript showCR:l]
+
+     c'hello\nworld\nisnt\nthis\n\nnice\n' asCollectionOfLinesDo:[:l | Transcript showCR:l]
+     c'hello\nworld\nisnt\nthis\n\nnice\n' asStringCollection do:[:l | Transcript showCR:l]
+
+     c'hello\nworld\nisnt\nthis\n\nnice' asCollectionOfWordsDo:#transcribeCR
+     '    hello\n    world\n   isnt\n   this\n   nice\n  ' asCollectionOfLinesDo:#transcribeCR
+     'hello' asCollectionOfLinesDo:#transcribeCR
+     '' asCollectionOfLinesDo:#transcribeCR
+     '      ' asCollectionOfLinesDo:#transcribeCR
+    "
+
+    "Modified (comment): / 03-02-2019 / 13:08:15 / Claus Gittinger"
 !
 
 asCollectionOfLinesWithReturn
-    "return a collection containing the lines (separated by cr)
-     of the receiver. If multiple cr's occur in a row, the result will
-     contain empty strings."
+    "return a collection containing the lines (separated by cr) of the receiver. 
+     If multiple cr's occur in a row, the result will contain empty strings."
 
     |lines|
 
@@ -3200,13 +3708,15 @@
      '1\2\3\' withCRs asCollectionOfLinesWithReturn
      '' withCRs asCollectionOfLinesWithReturn
     "
+
+    "Modified (comment): / 03-07-2018 / 10:59:47 / Claus Gittinger"
 !
 
 asCollectionOfSubstringsSeparatedBy:aCharacter
-    "return a collection containing substrings (separated by aCharacter)
-     of the receiver.
+    "return a collection containing substrings (separated by aCharacter) of the receiver.
      If aCharacter occurs multiple times in a row, the result will contain empty strings.
-     If the receiver ends with aCharacter, an empty string with be the last result element."
+     If the receiver starts with aCharacter, an empty string with be the first result element.
+     If the receiver ends with aCharacter, NO empty string with be the last result element."
 
     ^ self asCollectionOfSubCollectionsSeparatedBy:aCharacter
 
@@ -3215,12 +3725,13 @@
      '1 one:2 two:3 three:4 four:5 five:' asCollectionOfSubstringsSeparatedBy:$:
      '1 one 2 two 3 three 4 four 5 five' asCollectionOfSubstringsSeparatedBy:Character space
     "
+
+    "Modified (comment): / 11-02-2019 / 23:54:20 / Claus Gittinger"
 !
 
 asCollectionOfSubstringsSeparatedBy:aCharacter exceptIn:ch
-    "return a collection containing the substrings (separated by aCharacter)
-     of the receiver. If aCharacter occurs multiple times in a row,
-     the result will contain empty strings.
+    "return a collection containing the substrings (separated by aCharacter) of the receiver. 
+     If aCharacter occurs multiple times in a row, the result will contain empty strings.
      The separation is not done, inside a matching pair of ch-substrings.
      Can be used to tokenize csv-like strings, which may or may not be enclosed in quotes."
 
@@ -3261,6 +3772,8 @@
      'asd''f;d''dd;s' asCollectionOfSubstringsSeparatedBy:$; exceptIn:$'
     "
     "/ 'asd "hello bla" foo "bla bla" bar' asCollectionOfSubstringsSeparatedBy:$  exceptIn:$"
+
+    "Modified (comment): / 03-07-2018 / 11:00:02 / Claus Gittinger"
 !
 
 asCollectionOfSubstringsSeparatedBy:aFieldSeparatorString textSeparator:aTextSeparatorOrNil
@@ -3274,14 +3787,16 @@
         ^ self asCollectionOfSubstringsSeparatedByAll: aFieldSeparatorString
     ].
     sz := aTextSeparatorOrNil size.
-    sz = 0 ifTrue:[
+    sz == 0 ifTrue:[
         aTextSeparatorChar := aTextSeparatorOrNil
-    ] ifFalse:[sz = 1  ifTrue:[
-        "this is a String. Fetch the first character - compatibility to older expecco libs"
-        aTextSeparatorChar := aTextSeparatorOrNil first.
     ] ifFalse:[
-        self error:'textSeparatorSize > 1'.
-    ]].
+        sz == 1 ifTrue:[
+            "this is a String. Fetch the first character - compatibility to older expecco libs"
+            aTextSeparatorChar := aTextSeparatorOrNil first.
+        ] ifFalse:[
+            self error:'textSeparatorSize > 1'.
+        ]
+    ].
 
     items := OrderedCollection new.
 
@@ -3335,8 +3850,8 @@
 !
 
 asCollectionOfSubstringsSeparatedByAll:aSeparatorString
-    "return a collection containing the lines (separated by aSeparatorString)
-     of the receiver. If aSeparatorString occurs multiple times in a row,
+    "return a collection containing the lines (separated by aSeparatorString) of the receiver. 
+     If aSeparatorString occurs multiple times in a row, 
      the result will contain empty strings."
 
     ^ self asCollectionOfSubCollectionsSeparatedByAll:aSeparatorString
@@ -3344,6 +3859,8 @@
     "
      '1::2::3::4::5::' asCollectionOfSubstringsSeparatedByAll:'::'
     "
+
+    "Modified (comment): / 03-07-2018 / 11:00:16 / Claus Gittinger"
 !
 
 asCollectionOfSubstringsSeparatedByAny:aCollectionOfSeparators
@@ -3376,6 +3893,7 @@
 
     "
      'hello world isnt this nice' asCollectionOfWords
+     'hello world isnt this nice' asCollectionOfWordsDo:#transcribeCR
      '    hello    world   isnt   this   nice  ' asCollectionOfWords
      'hello' asCollectionOfWords
      '' asCollectionOfWords
@@ -3383,13 +3901,17 @@
      ' foo bar__baz__bla__ bar ' asCollectionOfWords
      ' foo __bar__baz__bla__ bar ' asCollectionOfWords
     "
+
+    "Modified (comment): / 03-02-2019 / 13:07:57 / Claus Gittinger"
 !
 
 asCollectionOfWordsDo:aBlock
     "evaluate aBlock for each word (separated by whitespace) of the receiver.
      Multiple occurrences of whitespace characters will be treated like one
      - i.e. whitespace is skipped.
-     Returns the number of words (i.e. the number of invocations of aBlock)."
+     Returns the number of words (i.e. the number of invocations of aBlock).
+     This is the same as 'asCollectionOfWords do:...' but avoids the creation of
+     a temporary collection."
 
     |count  "{ Class:SmallInteger }"
      start  "{ Class:SmallInteger }"
@@ -3417,11 +3939,14 @@
 
     "
      'hello world isnt this nice' asCollectionOfWordsDo:[:w | Transcript showCR:w]
+     'hello world isnt this nice' asCollectionOfWordsDo:#transcribeCR
      '    hello    world   isnt   this   nice  ' asCollectionOfWordsDo:[:w | Transcript showCR:w]
      'hello' asCollectionOfWordsDo:[:w | Transcript showCR:w]
      '' asCollectionOfWordsDo:[:w | Transcript showCR:w]
      '      ' asCollectionOfWordsDo:[:w | Transcript showCR:w]
     "
+
+    "Modified (comment): / 03-02-2019 / 13:08:15 / Claus Gittinger"
 !
 
 asDenseUnicodeString
@@ -3447,6 +3972,8 @@
      'abc' asUnicode16String asDenseUnicodeString
      'abc' asUnicode32String asDenseUnicodeString
      ('abc',(Character value:16r165)) asDenseUnicodeString
+     ('abc',(Character value:16r165)) copyTo:3
+     (('abc',(Character value:16r165)) copyTo:3) asDenseUnicodeString
      ('abc',(Character value:16r165)) asUnicode32String asDenseUnicodeString
     "
 
@@ -3515,6 +4042,20 @@
     "
 !
 
+asImmutableCollection
+    "fallback for subclasses of me which are not single byte strings.
+     return myself"
+
+    ^ self
+!
+
+asImmutableString
+    "fallback for subclasses of me which are not single byte strings.
+     return myself"
+
+    ^ self
+!
+
 asInteger
     "convert the receiver into an integer.
      Notice, that errors may occur during the read,
@@ -3676,12 +4217,25 @@
     "
 !
 
+asPackageId
+    "given a package-string as receiver, return a packageId object.
+     packageIds hide the details of module/directory handling inside the path.
+     See PackageId for the required format of those strings."
+
+    ^ PackageId from: self string
+
+    "
+     'stx:libbasic' asPackageId
+    "
+
+    "Created: / 11-07-2017 / 18:24:47 / cg"
+!
+
 asSingleByteStringIfPossible
     "if possible, return the receiver converted to a 'normal' string.
      It is only possible, if there are no characters with codePoints above 255 in the receiver.
      If not possible, the (wideString) receiver is returned."
 
-    self isWideString ifFalse:[^ self].
     self containsNon8BitElements ifTrue:[^ self].
     ^ self asSingleByteString
 
@@ -3728,7 +4282,52 @@
 
     ^ StringCollection fromString:self "string"
 
-    "Modified: 13.5.1996 / 20:36:59 / cg"
+    "
+     'hello\world\1\2\3' withCRs asStringCollection first    
+    "
+
+    "Modified: / 13-05-1996 / 20:36:59 / cg"
+    "Modified (comment): / 13-03-2017 / 14:05:14 / cg"
+!
+
+asStringWithBitsPerCharacterAtLeast:numRequiredBitsPerCharacter
+    "return the receiver in a representation which supports numRequiredBitsPerCharacter.
+     I.e. if required, convert to a Unicode16 or Unicode32 string"
+
+    numRequiredBitsPerCharacter > 8 ifTrue:[
+        numRequiredBitsPerCharacter > 16 ifTrue:[
+            ^ self asUnicode32String
+        ].    
+        numRequiredBitsPerCharacter > self bitsPerCharacter ifTrue:[
+            ^ self asUnicode16String
+        ].    
+    ].    
+    ^ self
+    
+    "
+     self assert:('abc' asStringWithBitsPerCharacterAtLeast:8) bitsPerCharacter == 8.
+     self assert:('abc' asStringWithBitsPerCharacterAtLeast:16) bitsPerCharacter == 16.
+     self assert:('abc' asStringWithBitsPerCharacterAtLeast:32) bitsPerCharacter == 32.
+
+     self assert:('abc' asUnicode16String asStringWithBitsPerCharacterAtLeast:8) bitsPerCharacter == 16.
+     self assert:('abc' asUnicode16String asStringWithBitsPerCharacterAtLeast:16) bitsPerCharacter == 16.
+     self assert:('abc' asUnicode16String asStringWithBitsPerCharacterAtLeast:32) bitsPerCharacter == 32.
+
+     self assert:('abc' asUnicode32String asStringWithBitsPerCharacterAtLeast:8) bitsPerCharacter == 32.
+     self assert:('abc' asUnicode32String asStringWithBitsPerCharacterAtLeast:16) bitsPerCharacter == 32.
+     self assert:('abc' asUnicode32String asStringWithBitsPerCharacterAtLeast:32) bitsPerCharacter == 32.
+    "
+
+    "Created: / 26-05-2019 / 12:47:07 / Claus Gittinger"
+!
+
+asStringWithoutEmphasis
+    "return myself as a string without any emphasis"
+    "return myself - I am a string"
+
+    ^ self
+
+    "Created: / 29-08-2018 / 09:21:07 / Claus Gittinger"
 !
 
 asSymbol
@@ -3810,6 +4409,21 @@
     "Created: 12.5.1996 / 10:41:14 / cg"
 !
 
+asTimeDuration
+    "return an TimeDuration object from the parsing the receiver string"
+
+    ^ TimeDuration readFromString:self
+
+   "
+     Time now asTimeDuration
+     10 asTimeDuration
+     10 seconds asTimeDuration
+     '10m 20s' asTimeDuration
+    "
+
+    "Created: / 21-01-2019 / 10:29:51 / Claus Gittinger"
+!
+
 asTimestamp
     "convert the receiver into an Timestamp.
      Notice, that errors may occur during the read,
@@ -3921,7 +4535,12 @@
      'http://www.exept.de:80/index.html' asURL port
      'http://www.exept.de:80/index.html' asURL method
      'http://www.exept.de:80/index.html' asURL path
-    "
+     'file:///tmp/index.html' asURL path
+     'file:///tmp/index.html' asURL method
+     'file:///tmp/index.html' asURL asString
+    "
+
+    "Modified (format): / 25-05-2019 / 09:33:18 / Claus Gittinger"
 !
 
 asUUID
@@ -3958,6 +4577,14 @@
     "
         'abc' asUnicode16String
     "
+
+    "Modified (comment): / 28-05-2019 / 14:41:04 / Stefan Vogel"
+!
+
+asUnicode16StringReplaceInvalidWith:replacementCharacter
+    ^ self asUnicode16String
+
+    "Created: / 28-05-2019 / 12:15:44 / Stefan Vogel"
 !
 
 asUnicode16StringZ
@@ -3970,7 +4597,7 @@
      |sz|
 
      sz := self size.
-     (self at:sz) == (Character codePoint:0) ifTrue:[
+     (sz ~~ 0 and:[(self at:sz) == (Character codePoint:0)]) ifTrue:[
          ^ self asUnicode16String.
      ].
 
@@ -3980,6 +4607,7 @@
            yourself.
 
      "
+        '' asUnicode16StringZ
         'abc' asUnicode16StringZ
         'abc' asUnicode16String asUnicode16StringZ
      "
@@ -4106,6 +4734,25 @@
     "
 !
 
+asVersionNumberCollection
+    "Convert a string like 1.2.3a to an Array of numbers (or string, if not a number).
+     Remove zeroes from the end."
+
+    ^ (self asCollectionOfSubstringsSeparatedByAny:'.-_') asVersionNumberCollection.
+
+   "
+     '1' asVersionNumberCollection.
+     '1.1' asVersionNumberCollection.
+     '1.1a' asVersionNumberCollection.
+     '1.1.0' asVersionNumberCollection.
+     '01.01.0' asVersionNumberCollection.
+     'expecco_18_1_0' asVersionNumberCollection.
+    "
+
+    "Created: / 20-06-2018 / 11:23:53 / Stefan Vogel"
+    "Modified: / 20-06-2018 / 19:24:36 / Stefan Vogel"
+!
+
 literalArrayEncoding
     "encode myself as an array literal, from which a copy of the receiver
      can be reconstructed with #decodeAsLiteralArray."
@@ -4126,30 +4773,40 @@
 
 !CharacterArray methodsFor:'copying'!
 
-, aStringOrCharacter
+, aStringOrCharacterOrAnyOther
     "redefined to allow characters and mixed strings to be appended.
      This is nonStandard, but convenient"
 
-    |myWidth otherWidth|
-
-    aStringOrCharacter isCharacter ifTrue:[
-        ^ self copyWith:aStringOrCharacter
-    ].
-    aStringOrCharacter isText ifTrue:[
-        ^ 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)
+    |stringifiedArg 
+     newSpecies newString l1 l2 combinedLen|
+
+    aStringOrCharacterOrAnyOther isCharacter ifTrue:[
+        ^ self copyWith:aStringOrCharacterOrAnyOther
+    ].
+    aStringOrCharacterOrAnyOther isText ifTrue:[
+        ^ aStringOrCharacterOrAnyOther concatenateFromString:self
+    ].
+    stringifiedArg := aStringOrCharacterOrAnyOther asString.
+    stringifiedArg isString ifTrue:[
+        (stringifiedArg bitsPerCharacter) > (self bitsPerCharacter) ifTrue:[
+            newSpecies := stringifiedArg species.
+        ] ifFalse:[
+            newSpecies := self species.
         ].
-    ].
-    ^ super , aStringOrCharacter
+        l1 := self size.
+        l2 := stringifiedArg size.
+        combinedLen := l1 + l2.
+        newString := newSpecies uninitializedNew:combinedLen.    
+        newString 
+            replaceFrom:1 to:l1 with:self startingAt:1;
+            replaceFrom:l1+1 to:combinedLen with:stringifiedArg startingAt:1.
+        ^ newString
+    ].
+    ^ super , stringifiedArg
 
     "
      'hello' , $1
+     'hello' , (Character codePoint:1046)
      'hello' , '1'
      'hello' , (' world' asText allBold)
      'hello' , (JISEncodedString fromString:' world')
@@ -4157,9 +4814,16 @@
 
      Transcript showCR:
          (Text string:'hello' emphasis:#italic) , (Text string:' world' emphasis:#bold)
-    "
-
-    "Modified: 28.6.1997 / 00:13:17 / cg"
+
+     'hello',123,'world'
+     'hello' allBold,123,'world'
+     'hello',123,'world' allBold
+    "
+
+    "Modified: / 28-06-1997 / 00:13:17 / cg"
+    "Modified: / 27-03-2019 / 19:37:34 / Claus Gittinger"
+    "Modified: / 02-04-2019 / 10:39:28 / Maren"
+    "Modified (comment): / 02-04-2019 / 11:36:00 / Stefan Vogel"
 !
 
 ,, aString
@@ -4168,16 +4832,20 @@
     ^ (self copyWith:Character cr) , aString
 
    "
-     hello ,, world
      'hello' ,, 'world'
    "
+
+    "Modified (comment): / 25-09-2018 / 10:21:45 / Claus Gittinger"
 !
 
 chopTo:maxLen
     "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      in the middle have been removed for a total string length
-     of maxLen."
+     of maxLen.
+     See also contractAtBeginningTo:, contractAtEndTo: and contractTo:.
+     This is similar to contractTo:, but removes the characters,
+     whereas contractTo: replaces them by '...'"
 
     |sz n1 n2|
 
@@ -4190,11 +4858,11 @@
     ^ (self copyFrom:1 to:n1) , (self copyFrom:sz - n2 + 1)
 
     "
-     '12345678901234'   chopTo:15
-     '123456789012345'  chopTo:15
-     '1234567890123456' chopTo:15
+     '12345678901234'   chopTo:15    
+     '123456789012345'  chopTo:15    
+     '1234567890123456' chopTo:15    
      'aShortString' chopTo:15
-     'aVeryLongNameForAStringThatShouldBeShortened' chopTo:15
+     'aVeryLongNameForAStringThatShouldBeShortened' chopTo:15   
     "
 
     "Modified: / 24-10-2006 / 12:32:01 / cg"
@@ -4204,7 +4872,9 @@
     "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      at the beginning have been replaced by '...' for a total string length
-     of maxLen. Can be used to abbreviate long entries in tables."
+     of maxLen. 
+     Can be used to abbreviate long entries in tables.
+     See also contractAtEndTo:, contractTo: and chopTo:"
 
     |sz|
 
@@ -4227,11 +4897,11 @@
     "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      at the end have been replaced by '...' for a total string length
-     of maxLen. Can be used to abbreviate long entries in tables."
-
-    |sz|
-
-    (sz := self size) <= maxLen ifTrue:[ ^ self ].
+     of maxLen. 
+     Can be used to abbreviate long entries in tables.
+     See also contractAtBeginningTo:, contractTo: and chopTo:"
+
+    (self size <= maxLen) ifTrue:[ ^ self ].
 
     ^ (self copyTo:maxLen-3),'...'
 
@@ -4244,6 +4914,7 @@
     "
 
     "Modified: / 24-10-2006 / 12:32:26 / cg"
+    "Modified: / 23-02-2017 / 21:32:21 / mawalch"
 !
 
 contractLeftTo:maxLen
@@ -4252,15 +4923,17 @@
      near the first quarter have been replaced by '...' for a total string length
      of maxLen.
      Very similar to contractTo:, but better to abbreviate long filename entries,
-     where the right part is of more use than the left."
-
-    |sz "{ SmallInteger }"
-     halfSize quarterSize "{ SmallInteger }"
+     where the right part is of more interest than the left.
+    See also contractAtBeginningTo:, contractAtEndTo:, contractTo: and chopTo:"
+
+
+    |sz "{ Class:SmallInteger }" quarterSize "{ Class:SmallInteger }"
      leftEnd rightEnd rightStart|
 
-    (sz := self size) <= maxLen ifTrue:[ ^ self ].
-
-    halfSize := maxLen // 2.
+    (sz := self size) <= maxLen ifTrue:[ 
+        ^ self.
+    ].
+
     quarterSize := maxLen // 4.
     leftEnd := quarterSize-1.
     rightEnd := maxLen - leftEnd - 3.
@@ -4275,23 +4948,29 @@
      'aVeryLongNameForAStringThatShouldBeShortened' contractLeftTo:15
      'C:\Dokumente und Einstellungen\cg\work\bosch\dapas\hw_schnittstellen\DAPAS__HpibDLL.st' contractLeftTo:40
     "
+
+    "Modified: / 11-06-2020 / 17:37:10 / Stefan Vogel"
 !
 
 contractTo:maxLen
     "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      in the middle have been replaced by '...' for a total string length
-     of maxLen. Can be used to abbreviate long entries in tables."
-
-    |sz "{ SmallInteger }" leftSize rightSize|
-
-    (sz := self size) <= maxLen ifTrue:[ ^ self ].
-
-    rightSize := maxLen // 2.
-    leftSize := maxLen - rightSize.
-    leftSize := leftSize - 2.
-    rightSize := rightSize - 1.
-    ^ (self copyTo:leftSize),'...',(self copyFrom:(sz+1-rightSize))
+     of maxLen. 
+     Can be used to abbreviate long entries in tables.
+     See also contractAtBeginningTo:, contractAtEndTo: and chopTo:.
+     (This is similar to chopTo:, but replaces by '...',
+      whereas chopTo: removes characters)"
+
+    |sz "{ Class:SmallInteger }" leftSize rightSize "{ Class:SmallInteger }"|
+
+    (sz := self size) <= maxLen ifTrue:[ 
+        ^ self.
+    ].
+
+    rightSize := (maxLen // 2) - 1.
+    leftSize := maxLen - rightSize - 3.
+    ^ (self copyTo:leftSize), '...', (self copyFrom:(sz+1-rightSize))
 
     "
      '12345678901234' contractTo:15
@@ -4307,6 +4986,39 @@
     "
 
     "Modified (comment): / 24-11-2011 / 19:17:46 / cg"
+    "Modified: / 11-06-2020 / 17:41:13 / Stefan Vogel"
+!
+
+copyBetween:string1 and:string2 caseSensitive:caseSensitive
+    "return the substring between two matching sub-strings.
+     Returns nil, if not both subStrings are present in the receiver."
+
+    |idx1 leftIndex rightIndex|
+
+    idx1 := self indexOfString:string1 caseSensitive:caseSensitive.
+    idx1 ~~ 0 ifTrue:[
+        leftIndex := (idx1 + string1 size).
+        rightIndex := self indexOfString:string2 caseSensitive:caseSensitive startingAt:leftIndex.
+        rightIndex ~~ 0 ifTrue:[
+            ^ self copyFrom:leftIndex to:rightIndex-1
+        ]
+    ].
+    ^ nil
+    
+    "
+     'hello funny world' copyBetween:'hello' and:'world' caseSensitive:true -> ' funny '
+     'helloworld' copyBetween:'hello' and:'world' caseSensitive:true -> ''
+     'helloorld' copyBetween:'hello' and:'world' caseSensitive:true -> nil
+
+     'hello funny World' copyBetween:'hello' and:'world' caseSensitive:true -> nil
+     'helloWorld' copyBetween:'hello' and:'world' caseSensitive:true -> nil
+
+     'hello funny World' copyBetween:'hello' and:'world' caseSensitive:false -> ' funny '
+     'helloWorld' copyBetween:'hello' and:'world' caseSensitive:false -> ''
+     'bla { foo }' copyBetween:'{' and:'}' caseSensitive:true -> ' foo '
+    "
+
+    "Created: / 08-06-2018 / 14:50:17 / Claus Gittinger"
 !
 
 copyReplaceAll:oldElement with:newElement
@@ -4315,16 +5027,18 @@
 
     "/ 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:[
+    oldElement isString ifTrue:[
+        newElement isString ifTrue:[
             ^ self copyReplaceString:oldElement withString:newElement.
         ].
-        self halt:'check if this is legal'.
-    ].
-    newElement isByteCollection ifTrue:[
-        self halt:'check if this is legal'.
+        self halt:'check if this is legal (trying to replace string by non-string)'.
+    ].
+    newElement isString ifTrue:[
+        self halt:'check if this is legal (trying to replace non-string by string)'.
     ].
     ^ super copyReplaceAll:oldElement with:newElement
+
+    "Modified: / 03-12-2018 / 16:03:32 / Stefan Vogel"
 !
 
 copyReplaceString:subString withString:newString
@@ -4351,6 +5065,9 @@
      '12345678901234567890' copyReplaceString:'123' withString:'OneTwoThree'
      '12345678901234567890' copyReplaceString:'123' withString:'*'
      '12345678901234567890' copyReplaceString:'234' withString:'foo'
+     '12345678901234567890' asUnicode16String copyReplaceString:'234' asUnicode16String withString:'foo'
+     '12345678901234567890' asUnicode16String copyReplaceString:'234' withString:'foo'
+     '12345678901234567890' asUnicode16String copyReplaceString:'234' withString:'foo' asUnicode16String
 
      ('a string with spaces' copyReplaceAll:$  withAll:' foo ')
         copyReplaceString:'foo' withString:'bar'
@@ -4381,9 +5098,11 @@
 !
 
 restAfter:keyword withoutSeparators:strip
-    "compare the left of the receiver with keyword,
-     if it matches return the right.
+    "compare the left part of the receiver with keyword,
+     if it matches return the right rest.
      Finally, if strip is true, remove whiteSpace.
+     If the string does not start with keyword, return nil.
+     
      This method is used to match and extract lines of the form:
         something: rest
      where we are interested in rest, but only if the receiver string
@@ -4414,7 +5133,8 @@
      'foo:     hello world    ' restAfter:'foo:' withoutSeparators:false
     "
 
-    "Created: 25.11.1995 / 11:04:18 / cg"
+    "Created: / 25-11-1995 / 11:04:18 / cg"
+    "Modified (comment): / 27-09-2018 / 10:01:55 / Claus Gittinger"
 !
 
 splitAtString:subString withoutSeparators:strip
@@ -4434,7 +5154,7 @@
         ].
         ^ StringCollection with:left with:right
     ].
-    self error:'substring not present in receiver' mayProceed:true.
+    self proceedableError:'substring not present in receiver'.
     ^ self
 
     "
@@ -4444,7 +5164,8 @@
      'hello > error' splitAtString:'->' withoutSeparators:true
     "
 
-    "Created: 25.11.1995 / 11:04:18 / cg"
+    "Created: / 25-11-1995 / 11:04:18 / cg"
+    "Modified: / 24-05-2018 / 14:55:52 / Claus Gittinger"
 ! !
 
 !CharacterArray methodsFor:'displaying'!
@@ -4497,6 +5218,7 @@
     "change the action block of all characters.
      Some widgets use this like a href if clicked onto the text."
 
+    Text isNil ifTrue:[^ self].
     ^ self asText actionForAll:aBlock
 !
 
@@ -4513,6 +5235,20 @@
     "
 !
 
+allGray
+    "return a text object representing the receiver, but in gray color.
+     This is used so often, that it's worth a utility here"
+
+    Text isNil ifTrue:[^ self].
+    ^ self withColor:Color gray
+
+    "
+     Transcript showCR:'hello' asText allBold allGray
+     Transcript showCR:'hello' allBold allGray
+     Transcript showCR:'hello' allGray
+    "
+!
+
 allItalic
     "return a text object representing the receiver, but all in italic"
 
@@ -4526,6 +5262,29 @@
     "
 !
 
+allNonBold
+    "make all characters non-bold;
+     I already have no emphasis, so the receiver string is returned"
+
+    ^ self
+
+    "Created: / 13-03-2019 / 21:02:45 / Claus Gittinger"
+!
+
+allRed
+    "return a text object representing the receiver, but in red color.
+     This is used so often, that it's worth a utility here"
+
+    Text isNil ifTrue:[^ self].
+    ^ self withColor:Color red
+
+    "
+     Transcript showCR:'hello' asText allBold allRed
+     Transcript showCR:'hello' allBold allRed
+     Transcript showCR:'hello' allRed
+    "
+!
+
 allStrikedOut
     "return a text object representing the receiver, but all in strikeout"
 
@@ -4561,6 +5320,17 @@
     ^ (self actionForAll:aBlock) withColor:(Color blue)
 !
 
+asActionLinkTo:aBlock info:tooltipMessage
+    "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).
+     Caveat: currently the tooltipMessage is ignored (there is no mechanism for that, yet)"
+
+    |a|
+    a := Explainer::ActionWithInfo block:aBlock info:tooltipMessage.
+    ^ (self actionForAll:a) withColor:(Color blue)
+!
+
 colorizeAllWith:aColor
     "return a text object representing the receiver, but all colorized"
 
@@ -4593,9 +5363,10 @@
      Since characterArrays do not hold any emphasis information,
      nil (no emphasis) is returned here."
 
-    ^ RunArray new:self size withAll:nil
-
-    "Created: 14.5.1996 / 13:58:58 / cg"
+    ^ RunArray new:(self size) withAll:nil
+
+    "Created: / 14-05-1996 / 13:58:58 / cg"
+    "Modified (format): / 08-06-2018 / 12:01:59 / Claus Gittinger"
 !
 
 emphasis:emphasisCollection
@@ -4616,8 +5387,8 @@
     "Created: 11.5.1996 / 14:13:27 / cg"
 !
 
-emphasisAtPoint:aPoint on:aGC
-    "return the emphasis at a given point, or nil if there is none"
+emphasisAtX:xOffset on:aGC
+    "return the emphasis at a given x offset, or nil if there is none"
 
     ^ nil
 !
@@ -4684,6 +5455,29 @@
     "Created: / 13-12-1999 / 21:49:24 / cg"
 !
 
+withBackgroundColor:aColorOrColorSymbol
+    "return a text object representing the receiver, but with all background colorized.
+     Usage of a colorSymbol is considered bad style (provided for backward compatibility);
+     please change to pass a proper color 
+     (makes it easier to find color uses)"
+
+    |color|
+    
+    aColorOrColorSymbol isSymbol ifTrue:[
+        color := (Color perform:aColorOrColorSymbol)
+    ] ifFalse:[
+        color := aColorOrColorSymbol
+    ].    
+    ^ self asText backgroundColorizeAllWith:color
+
+    "
+     Transcript showCR:('hello' withBackgroundColor:#red)
+     Transcript showCR:('world' withColor:#red)
+     Transcript showCR:('hello' withBackgroundColor:Color red)
+     Transcript showCR:('world' withColor:Color green darkened)
+    "
+!
+
 withColor:aColorOrColorSymbol
     "return a text object representing the receiver, but all colorized.
      Usage of a colorSymbol is considered bad style (provided for backward compatibility);
@@ -4707,6 +5501,32 @@
     "
 !
 
+withColor:foregroundColorOrColorSymbol on:backgroundColorOrColorSymbol
+    "return a text object representing the receiver, but all colorized with both fg and bg.
+     Usage of a colorSymbol is considered bad style (provided for backward compatibility);
+     please change to pass a proper color 
+     (makes it easier to find color uses)"
+
+    |fgColor bgColor|
+    
+    foregroundColorOrColorSymbol isSymbol ifTrue:[
+        fgColor := (Color perform:foregroundColorOrColorSymbol)
+    ] ifFalse:[
+        fgColor := foregroundColorOrColorSymbol
+    ].    
+    backgroundColorOrColorSymbol isSymbol ifTrue:[
+        bgColor := (Color perform:backgroundColorOrColorSymbol)
+    ] ifFalse:[
+        bgColor := backgroundColorOrColorSymbol
+    ].    
+    ^ self colorizeAllWith:fgColor on:bgColor
+
+    "
+     Transcript showCR:('hello' withColor:#red on:#blue)
+     Transcript showCR:('hello' withColor:Color red on:Color blue)
+    "
+!
+
 withoutAnyColorEmphasis
     "for protocol compatibility with Text"
 
@@ -4723,6 +5543,14 @@
     "Modified (comment): / 06-03-2012 / 18:14:27 / cg"
 !
 
+withoutEmphasis
+    "for protocol compatibility with Text"
+
+    ^ self
+
+    "Created: / 13-03-2019 / 21:03:41 / Claus Gittinger"
+!
+
 withoutEmphasis:emphasisToRemove
     "for protocol compatibility with Text"
 
@@ -4749,12 +5577,12 @@
 
     |map outStream mapChar|
 
+    self containsNon7BitAscii ifFalse:[
+        ^ self  "/ I cannot contain any diacritical chars
+    ]. 
+
     map := self class unicodeDenormalizationMap.
-    
-    self containsNon7BitAscii ifFalse:[^ self]. "/ I cannot contain any
-
-    mapChar := 
-        [:char |
+    mapChar := [:char |
             |mappedChars|
 
             (mappedChars := map at:char ifAbsent:nil) notNil ifTrue:[ 
@@ -4772,8 +5600,10 @@
      'Ö' asDenormalizedUnicodeString 
      'aÖÄx' asDenormalizedUnicodeString 
      'abc' asDenormalizedUnicodeString 
-     'ṩ'  asString asDenormalizedUnicodeString 
-    "
+     'ṩ' asDenormalizedUnicodeString 
+    "
+
+    "Modified (format): / 02-01-2018 / 18:52:33 / stefan"
 !
 
 asNormalizedUnicodeString
@@ -4836,9 +5666,11 @@
     myEncoding := self encoding.
     encodingSymbol == myEncoding ifTrue:[^ self].
 
-    encoder := CharacterEncoder encoderToEncodeFrom:(self encoding) into:encodingSymbol.
+    encoder := CharacterEncoder encoderToEncodeFrom:myEncoding into:encodingSymbol.
     encoder isNil ifTrue:[^ self].
     ^ encoder decodeString:self.
+
+    "Modified: / 17-01-2018 / 17:34:43 / stefan"
 !
 
 encodeFrom:oldEncoding into:newEncoding
@@ -4850,6 +5682,17 @@
     "
 !
 
+encodeInto:newEncoding
+    ^ CharacterEncoder encodeString:self from:self encoding into:newEncoding
+
+    "
+     'äüö' encodeInto:#utf8
+     ('äüö' encodeInto:#utf8) decodeFrom:#utf8
+    "
+
+    "Created: / 17-01-2018 / 17:43:20 / stefan"
+!
+
 rot13
      "Usenet: from `rotate alphabet 13 places']
       The simple Caesar-cypher encryption that replaces each English
@@ -4954,97 +5797,20 @@
 !
 
 utf8EncodedOn:aStream
-    "return the UTF-8 representation of a Unicode string.
-     The resulting string is only useful to be stored on some external file,
-     not for being used inside ST/X."
-
-    |string 
-     stringSize "{ Class: SmallInteger }"
-     codePoint "{Class: SmallInteger }" 
-     v "{Class: SmallInteger }"
-     character b1 b2 b3 b4 b5|
-
-    string := self string.
-
-    "/ avoid creation of new strings if possible
-    string containsNon7BitAscii ifFalse:[
-        aStream nextPutAll:string asSingleByteString.
-        ^ self.
-    ].
-
-    stringSize := string size.
-
-    1 to:stringSize do:[:idx |
-        character := string at:idx.
-        codePoint := character codePoint.
-        codePoint < 16r80 ifTrue:[
-            aStream nextPutByte:codePoint.
-        ] ifFalse:[
-            b1 := (codePoint bitAnd:16r3F) bitOr:2r10000000.
-            v := codePoint bitShift:-6.
-            v <= 16r1F ifTrue:[
-                aStream nextPutByte:(v bitOr:2r11000000).
-                aStream nextPutByte:b1.
-            ] ifFalse:[
-                b2 := (v bitAnd:16r3F) bitOr:2r10000000.
-                v := v bitShift:-6.
-                v <= 16r0F ifTrue:[
-                    aStream nextPutByte:(v bitOr:2r11100000).
-                    aStream nextPutByte:b2; nextPutByte:b1.
-                ] ifFalse:[
-                    b3 := (v bitAnd:16r3F) bitOr:2r10000000.
-                    v := v bitShift:-6.
-                    v <= 16r07 ifTrue:[
-                        aStream nextPutByte:(v bitOr:2r11110000).
-                        aStream nextPutByte:b3; nextPutByte:b2; nextPutByte:b1.
-                    ] ifFalse:[
-                        b4 := (v bitAnd:16r3F) bitOr:2r10000000.
-                        v := v bitShift:-6.
-                        v <= 16r03 ifTrue:[
-                            aStream nextPutByte:(v bitOr:2r11111000).
-                            aStream nextPutByte:b4; nextPutByte:b3; nextPutByte:b2; nextPutByte:b1.
-                        ] ifFalse:[
-                            b5 := (v bitAnd:16r3F) bitOr:2r10000000.
-                            v := v bitShift:-6.
-                            v <= 16r01 ifTrue:[
-                                aStream nextPutByte:(v bitOr:2r11111100).
-                                aStream nextPutByte:b5; nextPutByte:b4; nextPutByte:b3; nextPutByte:b2; nextPutByte:b1.
-                            ] ifFalse:[
-                                "/ cannot happen - we only support up to 30 bit characters
-                                EncodingError raiseWith:character errorString:'codePoint > 31bit in #utf8Encode'.
-                            ]
-                        ].
-                    ].
-                ].
-            ].
-        ].
-    ].
-
-    "
-        String streamContents:[:s|
-            'hallo' utf8EncodedOn:s
-        ].
-
-        ByteArray streamContents:[:s|
-            'hallo' utf8EncodedOn:s
-        ].
-
-        String streamContents:[:s|
-            'abcdeäöüß' asUnicode32String utf8EncodedOn:s
-        ].
-.
-        ByteArray streamContents:[:s|
-            'abcdeäöüß' asUnicode32String utf8EncodedOn:s
-        ].
-
-        '/tmp/bytes' asFilename writingFileDo:[:s|
-            'abcdeäöüß' utf8EncodedOn:s
-        ].
-    "
+    "write the UTF-8 representation of myself to aStream."
+
+    aStream nextPutAllUtf8:self.
+
+    "Modified: / 16-02-2017 / 16:51:32 / stefan"
 ! !
 
-
-
+!CharacterArray methodsFor:'filling and replacing'!
+
+clearContents
+    "to be used with cryptographic keys, to wipe their contents after use"
+
+    self atAllPut:(Character value:0)
+! !
 
 !CharacterArray methodsFor:'matching - glob expressions'!
 
@@ -5052,6 +5818,7 @@
     "like match, but the receiver may be a compound match pattern,
      consisting of multiple simple GLOB patterns, separated by semicolons.
      This is usable with fileName pattern fields.
+     This is a case sensitive match: lower/uppercase are considered different.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
              NOT the ST-80 meaning.
@@ -5067,10 +5834,13 @@
      'f*;b*' match:'bar'
      'f*;b*' compoundMatch:'foo'
      'f*;b*' compoundMatch:'bar'
-    "
-
-    "Modified: / 30.1.1998 / 11:40:18 / stefan"
-    "Modified: / 16.12.1999 / 01:22:08 / cg"
+     '*.png;*.gif' compoundMatch:'bar.jpg'
+     '*.png;*.gif' compoundMatch:'bar.gif'
+    "
+
+    "Modified: / 30-01-1998 / 11:40:18 / stefan"
+    "Modified: / 16-12-1999 / 01:22:08 / cg"
+    "Modified (comment): / 02-03-2019 / 12:21:33 / Claus Gittinger"
 !
 
 compoundMatch:aString caseSensitive:caseSensitive
@@ -5095,11 +5865,32 @@
      'f*;b*' compoundMatch:'Foo' caseSensitive:false
      'f*;b*' compoundMatch:'Bar' caseSensitive:false
      'f*;b*' compoundMatch:'ccc' caseSensitive:false
-    "
-
-    "Modified: / 15.4.1997 / 15:50:33 / cg"
-    "Modified: / 30.1.1998 / 11:40:18 / stefan"
-    "Created: / 16.12.1999 / 01:21:35 / cg"
+
+     '*.png;*.gif' compoundMatch:'bar.GIF'
+     '*.png;*.gif' compoundMatch:'bar.GIF' caseSensitive:false 
+
+     'foo' compoundMatch:'bar' caseSensitive:false 
+     'Bar' compoundMatch:'bar' caseSensitive:false  
+     'bar' compoundMatch:'bar' caseSensitive:true   
+     'Bar' compoundMatch:'bar' caseSensitive:true       
+     'foo;Bar' compoundMatch:'bar' caseSensitive:false  
+     'foo;bar' compoundMatch:'bar' caseSensitive:true   
+     'foo;Bar' compoundMatch:'bar' caseSensitive:true   
+     'foo;bar' compoundMatch:'Bar' caseSensitive:false  
+     'foo;bar' compoundMatch:'Bar' caseSensitive:true   
+     'foo;bar' compoundMatch:'Bar' caseSensitive:true   
+     '.foo' compoundMatch:'.foo' caseSensitive:true   
+     '.foo' compoundMatch:'.Foo' caseSensitive:true   
+     '.foo' compoundMatch:'.Foo' caseSensitive:false   
+     'bar;.foo' compoundMatch:'.foo' caseSensitive:true     
+     'bar;.foo' compoundMatch:'.Foo' caseSensitive:true     
+     'bar;.foo' compoundMatch:'.Foo' caseSensitive:false    
+    "
+
+    "Modified: / 15-04-1997 / 15:50:33 / cg"
+    "Modified: / 30-01-1998 / 11:40:18 / stefan"
+    "Created: / 16-12-1999 / 01:21:35 / cg"
+    "Modified (comment): / 02-03-2019 / 12:22:14 / Claus Gittinger"
 !
 
 compoundMatch:aString caseSensitive:caseSensitive withoutSeparators:withoutSeparators
@@ -5117,9 +5908,10 @@
 
     matchers := self asCollectionOfSubstringsSeparatedBy:$;.
     withoutSeparators ifTrue:[ matchers := matchers collect:[:each | each withoutSeparators] ].
+
     ^ matchers
-        contains:[:aPattern |
-            aPattern match:aString caseSensitive:caseSensitive escapeCharacter:nil
+        contains:[:somePattern |
+            somePattern match:aString caseSensitive:caseSensitive escapeCharacter:nil
         ].
 
     "
@@ -5132,6 +5924,8 @@
      'f*;b*' compoundMatch:'Foo' caseSensitive:false
      'f*;b*' compoundMatch:'Bar' caseSensitive:false
      'f*;b*' compoundMatch:'ccc' caseSensitive:false
+     'f*;x*;bla.c' compoundMatch:'bla' caseSensitive:false  
+     'f*;x*;bla.c' compoundMatch:'bla.c' caseSensitive:false  
 
      'f* ; b*' compoundMatch:'foo'
      'f* ; b*' compoundMatch:'foo' caseSensitive:true withoutSeparators:true
@@ -5175,8 +5969,8 @@
 
 findMatchString:matchString
     "like findString/indexOfSubCollection, but allowing GLOB match patterns.
-     find matchstring; if found, return the index;
-     if not found, return 0.
+     find matchstring; if found, return the index, if not, return 0.
+     This is a case sensitive match: lower/uppercase are considered different.
 
      NOTICE: match-meta character interpretation is like in unix-matching,
              NOT the ST-80 meaning.
@@ -5189,12 +5983,34 @@
       1234567890123
      'hello world bla foo baz' findMatchString:'b* '
     "
+
+    "Modified (comment): / 02-03-2019 / 12:21:07 / Claus Gittinger"
+!
+
+findMatchString:matchString caseSensitive:caseSensitive
+    "like findString/indexOfSubCollection, but allowing GLOB match patterns.
+     find matchstring; if found, return the index, if not, return 0.
+     This is a case sensitive match: lower/uppercase are considered different.
+
+     NOTICE: match-meta character interpretation is like in unix-matching,
+             NOT the ST-80 meaning.
+     NOTICE: this GLOB, which is different from regex matching (see matchesRegex:)
+     NOTICE: the argument is the match pattern"
+
+    ^ self findMatchString:matchString startingAt:1 caseSensitive:caseSensitive ifAbsent:0
+
+    "
+      1234567890123
+     'hello world bla foo baz' findMatchString:'b* '
+    "
+
+    "Modified (comment): / 02-03-2019 / 12:21:07 / Claus Gittinger"
 !
 
 findMatchString:matchString startingAt:index
     "like findString, but allowing GLOB match patterns.
-     find matchstring, starting at index. if found, return the index;
-     if not found, return 0.
+     find matchstring, starting at index; if found, return the index, if not, return 0.
+     This is a case sensitive match: lower/uppercase are considered different.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
              NOT the ST-80 meaning.
@@ -5202,6 +6018,8 @@
      NOTICE: the argument is the match pattern"
 
     ^ self findMatchString:matchString startingAt:index caseSensitive:true ifAbsent:0
+
+    "Modified (comment): / 02-03-2019 / 12:21:05 / Claus Gittinger"
 !
 
 findMatchString:matchString startingAt:index caseSensitive:caseSensitive ifAbsent:exceptionBlock
@@ -5322,7 +6140,7 @@
                 s nextPut:ch
             ].
 
-        (String matchScanArrayFrom:self) do:[:matchEntry |
+        (self class matchScanArrayFrom:self) do:[:matchEntry |
             matchEntry isCharacter ifTrue:[
                 addCharacter value:matchEntry
             ] ifFalse:[
@@ -5336,7 +6154,7 @@
                             |set min max|
 
                             s nextPut:$[.
-                            set := matchEntry copy sort.
+                            set := matchEntry "copy sort". "/ already sorted
                             min := set min.
                             max := set max.
                             set asSet = (min to:max) asSet ifTrue:[
@@ -5348,7 +6166,7 @@
                             ].
                             s nextPut:$].
                         ] ifFalse:[
-                            self halt.
+                            self halt:'funny match entry'.
                         ].
                     ].
                 ].
@@ -5365,17 +6183,21 @@
      'h[0-9][0-9][0-9]' globPatternAsRegexPattern
      'h[0-9]*' globPatternAsRegexPattern
      'h[-+]*' globPatternAsRegexPattern
-
+     'h[abc]*' globPatternAsRegexPattern
+     'h[0-9abc]*' globPatternAsRegexPattern
      'hello world' matches:'h*w'
      'hello world' matchesRegex:('h*w' globPatternAsRegexPattern)
      'hello world' matches:'h*d'
      'hello world' matchesRegex:('h*d' globPatternAsRegexPattern)
     "
+
+    "Modified: / 03-12-2018 / 15:47:15 / Stefan Vogel"
 !
 
 includesMatchString:matchString
     "like includesString, but allowing GLOB match patterns.
-     find matchstring; if found, return true, otherwise return false.
+     find matchstring; if found, return true, false otherwise.
+     This is a case sensitive match: lower/uppercase are considered different.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
              NOT the ST-80 meaning.
@@ -5389,7 +6211,12 @@
      'hello world' includesMatchString:'h[aeiou]llo'
      'hello world' includesMatchString:'wor*'
      'hello world' includesMatchString:'woR*'
-    "
+     'menue' includesMatchString:'[mM]enu[Ee]'
+     'blamenuebla' includesMatchString:'[mM]enu[Ee]'
+     'blaMenuebla' includesMatchString:'[mM]enu[Ee]'
+    "
+
+    "Modified (comment): / 02-03-2019 / 12:20:58 / Claus Gittinger"
 !
 
 includesMatchString:matchString caseSensitive:caseSensitive
@@ -5417,14 +6244,25 @@
 
      'hello world' includesMatchString:'woR*' caseSensitive:true
      'hello world' includesMatchString:'woR*' caseSensitive:false
-    "
+
+     'menue' includesMatchString:'[mM]enu[Ee]'
+     'menue' includesMatchString:'[mM]enu[Ee]' caseSensitive:true
+     'blamenuebla' includesMatchString:'[mM]enu[Ee]'
+     'blamenuebla' includesMatchString:'[mM]enu[Ee]' caseSensitive:true
+
+     'blaMenuebla' includesMatchString:'[MS]enu[EF]'
+     'blaMenuebla' includesMatchString:'[MS]enu[EF]' caseSensitive:true
+     'blaMenuebla' includesMatchString:'[MS]enu[EF]' caseSensitive:false
+    "
+
+    "Modified (comment): / 02-03-2019 / 12:18:57 / Claus Gittinger"
 !
 
 match:aString
     "return true if aString matches self, where self may contain GLOB meta-match
      characters $* (to match any string) or $# (to match any character).
      or [...] to match a set of characters.
-     Lower/uppercase are considered different.
+     This is a case sensitive match: lower/uppercase are considered different.
      The escape character is the backQuote.
 
      NOTICE: match-meta character interpretation is like in unix-matching (glob),
@@ -5435,6 +6273,13 @@
     ^ self match:aString from:1 to:aString size caseSensitive:true
 
     "
+     '#f#' match:'afc'
+     '#f#' match:'aec'
+     '#f#' match:'ae'
+     '#f#' match:'a'
+     '#f#' match:'f'
+     '#f#' match:'ff'
+
      '\*f*' match:'f'
      '\*f*' match:'*f'
      '*\*f*' match:'*f'
@@ -5450,7 +6295,9 @@
      '*-hh' match:'anton-h'
     "
 
-    "Modified: / 9.6.1998 / 18:50:00 / cg"
+    "Modified: / 09-06-1998 / 18:50:00 / cg"
+    "Modified (comment): / 29-07-2017 / 14:00:23 / cg"
+    "Modified (comment): / 02-03-2019 / 12:20:48 / Claus Gittinger"
 !
 
 match:aString caseSensitive:caseSensitive
@@ -5593,21 +6440,20 @@
     |matchScanArray|
 
     "
-     keep the matchScanArray from the most recent match -
-     avoids parsing the pattern over-and over if multiple searches
-     are done with the same pattern.
-    "
-
+     keep the matchScanArray from the most recent matches -
+     avoids parsing the pattern over-and over again,
+     if multiple searches are done with the same pattern.
+    "
     (PreviousMatches isNil
     or:[(matchScanArray := PreviousMatches at: self ifAbsent:[nil]) isNil]) ifTrue:[
         matchScanArray := self class matchScanArrayFrom:self escapeCharacter:escape.
         matchScanArray isNil ifTrue:[
-            'CharacterArray [info]: invalid matchpattern:''' infoPrint. self infoPrint. ''' comparing for equality.' infoPrintCR.
+            ParseWarning raiseRequestErrorString:('CharacterArray [info]: invalid matchpattern: ''%1'' comparing for equality' bindWith:self).
             ^ self = aString
-"/            ^ false
+            "/ ^ false
         ].
         PreviousMatches isNil ifTrue:[
-            PreviousMatches := CacheDictionary new:10
+            PreviousMatches := CacheDictionary new:15
         ].
         PreviousMatches at:self put:matchScanArray.
     ].
@@ -5622,9 +6468,12 @@
     "
      '*ute*' match:'12345COMPUTER' from:1 to:5 caseSensitive:false
      '*ute*' match:'12345COMPUTER' from:6 to:13 caseSensitive:false
-    "
-
-    "Modified: / 10.11.1998 / 21:43:46 / cg"
+     
+     '*[12' match:'12345COMPUTER' from:6 to:13 caseSensitive:false -- gives a warning
+    "
+
+    "Modified: / 29-07-2017 / 14:01:42 / cg"
+    "Modified (comment): / 24-10-2018 / 09:01:31 / Claus Gittinger"
 !
 
 match:aString from:start to:stop ignoreCase:ignoreCase
@@ -5763,7 +6612,7 @@
     "Modified: 2.4.1997 / 17:28:58 / cg"
 !
 
-matches:aPatternString
+matches:aGlobPatternString
     "return true if the receiver matches aString, where aPatternString may contain GLOB meta-match
      characters $* (to match any string) or $# (to match any character).
      or [...] to match a set of characters.
@@ -5774,7 +6623,9 @@
      NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
      NOTICE: the receiver is the match pattern"
 
-    ^ aPatternString match:self
+    ^ aGlobPatternString match:self
+
+    "Modified (format): / 18-08-2018 / 20:51:45 / Claus Gittinger"
 !
 
 matches:aPatternString caseSensitive:caseSensitive
@@ -5807,7 +6658,34 @@
     "Created: / 08-03-2012 / 03:11:11 / cg"
 ! !
 
-
+!CharacterArray methodsFor:'matching - regex'!
+
+subExpressionsInRegex:rxString caseSensitive:caseSensitive
+    "return the collection of matching regex-subexpressions.
+     Subexpressions are sub-patterns enclosed in parentheses in the regex.
+     substrings in the receiver.
+     Returns nil, if there is no match.
+     Use this to extract particular parts from the receiver.
+     Refer to `documentation' protocol of RxParser class for details."
+
+     |matcher|
+
+     matcher := Regex::RxMatcher new initializeFromString:rxString ignoreCase:caseSensitive not.
+     (matcher matches:self) ifTrue:[
+        ^ matcher subexpressions
+     ].
+     "/ no match
+     ^ nil.
+
+    "
+     'I am Tim Dalton' subExpressionsInRegex:'I am (.+)' caseSensitive:false   
+     'i am Boris Johnson' subExpressionsInRegex:'I am (.+)' caseSensitive:false  
+     'you are Boris Johnson' subExpressionsInRegex:'(i|you) (am|are) (.+)' caseSensitive:false  
+     '1234abc3456' subExpressionsInRegex: '([0-9]+)abc([0-9]+)' caseSensitive:false   
+    "
+
+    "Modified (comment): / 14-07-2020 / 20:15:36 / cg"
+! !
 
 !CharacterArray methodsFor:'padded copying'!
 
@@ -5951,9 +6829,9 @@
 
 paddedTo:newSize
      "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."
+      plus spaces up to length.
+      If the receiver's size is equal or greater than the length argument,
+      the original receiver is returned unchanged."
 
      ^ self paddedTo:newSize with:(Character space)
 
@@ -5962,6 +6840,8 @@
      123 printString paddedTo:10
      '12345678901234' paddedTo:10
     "
+
+    "Modified (format): / 21-03-2019 / 12:56:24 / Claus Gittinger"
 ! !
 
 !CharacterArray methodsFor:'printing & storing'!
@@ -5974,7 +6854,9 @@
     |firstChar secondChar thirdChar|
 
     firstChar := (self at:1) asLowercase.
-    ((firstChar isVowel and:[firstChar ~~ $u]) or:[firstChar == $x]) ifTrue:[
+    ((firstChar isVowel and:[firstChar ~~ $u]) 
+      or:[firstChar == $x]
+    ) ifTrue:[
         ^ 'an'
     ].
 
@@ -5982,12 +6864,21 @@
         secondChar := (self at:2) asLowercase.
 
         "/ may need more here...
-        ( #('rb') includes:(String with:firstChar with:secondChar)) ifTrue:[
+        (firstChar == $r 
+          and:[secondChar == $b]
+        ) ifTrue:[
             ^ 'an'
         ].
 
         thirdChar := (self at:3) asLowercase.
 
+        (firstChar == $s 
+          and:[secondChar == $c 
+          and:[thirdChar == $h]]
+        ) ifTrue:[
+            ^ 'a'
+        ].
+
         (firstChar isVowel not
         and:[(secondChar isVowel or:[secondChar == $y]) not
         and:[thirdChar isVowel not ]]) ifTrue:[
@@ -6009,23 +6900,25 @@
     ^ '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.
+     'scheme' article.
     "
 
     "Modified (comment): / 01-05-2016 / 10:57:25 / cg"
+    "Modified (comment): / 03-04-2019 / 10:08:57 / Claus Gittinger"
 !
 
 basicStoreString
@@ -6069,12 +6962,28 @@
      (although the fallBack is to display its printString ...)"
 
     "/ 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) ifTrue:[
-        self storeOn:aGCOrStream.
-        ^ self
-    ].
-    ^ super displayOn:aGCOrStream
+    "/ old ST80 means: draw-yourself on a GC.
+    aGCOrStream isStream ifFalse:[
+        ^ super displayOn:aGCOrStream.
+    ].
+
+    self storeOn:aGCOrStream.
+
+    "Modified: / 22-02-2017 / 16:59:25 / cg"
+!
+
+htmlString
+    "for compatibility with HTML-dom nodes.
+     Generates a possibly escaped string for HTML"
+
+    ^ HTMLUtilities escapeCharacterEntities:self 
+
+    "
+     'foo<bar>baz' htmlString   
+     ('foo<',(Character value:0x250),'>baz') htmlString
+     'foo bar baz' htmlString
+     ('foo ',(Character value:0x250),' baz') htmlString
+    "
 !
 
 printOn:aStream
@@ -6089,6 +6998,76 @@
     ^ self
 !
 
+printWithCEscapesOn:aStream
+    "append the receiver's characters
+     with all special and unprintable characters replaced by \X-character escapes.
+     (similar to the way C-language literal Strings are represented).
+     The resulting string will contain only 7-bit ascii characters.
+     Emphasis is not supported.
+     The following escapes are generated:
+        \'      single quote character
+        \dQuote double quote character
+        \b      backspace character
+        \r      return character
+        \n      newline character
+        \t      tab character
+        \\      the \ character itself
+        \xnn    two digit hex number defining the characters ascii value
+        \unnnn  four digit hex number defining the characters ascii value
+        \Unnnnnnnn  eight digit hex number defining the characters ascii value
+
+     Sigh: this is named completely wrong (opposite naming of withCRs/witoutCRs),
+           but it cannot be changed easily, as these methods are already used heavily
+    "
+
+    self hasChangeOfEmphasis ifTrue:[ self error:'emphasis not supported' ].
+
+    self do:[:ch |
+        |cp seq|
+
+        (ch == $' or:[ch == $" or:[ch == $\]]) ifTrue:[
+            aStream nextPut:$\.
+            aStream nextPut:ch.
+        ] ifFalse:[
+            (ch codePoint between:32 and:126) ifTrue:[
+                aStream nextPut:ch
+            ] ifFalse:[
+                ch == Character return ifTrue:[
+                    seq := '\r'
+                ] ifFalse:[ ch == Character nl ifTrue:[
+                    seq := '\n'
+                ] ifFalse:[ ch == Character backspace ifTrue:[
+                    seq := '\b'
+                ] ifFalse:[ ch == Character tab ifTrue:[
+                    seq := '\t'
+                ] ifFalse:[ ch == $\ ifTrue:[
+                    seq := '\\'
+                ] ifFalse:[
+                    cp := ch codePoint.
+                    cp <= 16rFF ifTrue:[
+                        seq := '\x' , (cp printStringRadix:16 size:2 fill:$0)
+                    ] ifFalse:[
+                        cp <= 16rFFFF ifTrue:[
+                            seq := '\u' , (cp printStringRadix:16 size:4 fill:$0)
+                        ] ifFalse:[
+                            seq := '\U',(cp printStringRadix:16 size:8 fill:$0)
+                        ]
+                    ]
+                ]]]]].
+                aStream nextPutAll:seq
+            ].
+        ].
+    ].
+
+    "
+     'c:\foo\bar\baz' printWithCEscapesOn:Transcript.  
+     c'hello\n\tworld' printWithCEscapesOn:Transcript.
+     'hello\b\tworld' withoutCEscapes printWithCEscapesOn:Transcript.
+     'hello\nworld\na\n\tnice\n\t\tstring' withoutCEscapes printWithCEscapesOn:Transcript.
+     ('hello ',(Character value:16r1234),' world') printWithCEscapesOn:Transcript
+    "
+!
+
 printWithQuotesDoubledOn:aStream
     "put the raw storeString of myself on aStream"
 
@@ -6103,9 +7082,14 @@
 
 printXmlQuotedOn:aStream
     "convert aString to a valid XML string
-     that can be used for attributes, text, comments an PIs
+     that can be used for XML attributes.
+     Can also be used for XML text, but better use #printXmlTextQuotedOn:.
+     Various senders expect, that the output is ISO-8859-1 compatible
+     (they don't care for encoding), so for now, we always generate 8-bit chars.
      TODO: care for 16bit UNICODE string and escape chars ..."
 
+    <resource: #todo>
+
     self do:[:eachChar |
         eachChar == $< ifTrue:[
             aStream nextPutAll:'&lt;'     "mapping needed for xml text"
@@ -6120,70 +7104,89 @@
         ] ifFalse:[
             |codePoint|
             codePoint := eachChar codePoint.
-            (codePoint < 16r20 or:[codePoint >= 16r7F]) ifTrue:[
+            (codePoint < 16r20 
+             or:[codePoint >= 16r7F 
+                 and:[codePoint <= 16r9F 
+                      or:[codePoint > 16rFF] "for now, always make sure, that output is ISO-8859-1 compatible"]
+            ]) ifTrue:[
                 aStream nextPutAll:'&#'.
-                codePoint printOn:aStream.
+                codePoint printOn:aStream base:16.
                 aStream nextPut:$;.
-        ] ifFalse:[
-            aStream nextPut:eachChar
-        ]]]]]]
-    ].
+            ] ifFalse:[
+                aStream nextPut:eachChar
+            ].
+        ]]]]]
+    ].
+
+    "Modified: / 03-12-2018 / 15:21:27 / Stefan Vogel"
 !
 
 printXmlTextQuotedOn:aStream
+    <resource: #todo>
     "convert aString to a valid XML string
      that can be used for XML text.
      Here line formatting characters are not escaped.
-     TODO: care for 16bit UNICODE string and escape chars ..."
+     For XML text (as opposed to XML attribute), $' and $"" need
+     not to be transliterated (see https://www.w3.org/TR/xml Section 2.4).
+     Various senders expect, that the output is ISO-8859-1 compatible
+     (they don't care for encoding), so for now, we always generate 8-bit chars.
+     TODO: care for 16bit UNICODE string and escape chars 
+            - but we need to know the XML file encoding"
 
     self do:[:eachChar |
         eachChar == $< ifTrue:[
             aStream nextPutAll:'&lt;'     "mapping needed for xml text"
         ] ifFalse:[ eachChar == $& ifTrue:[
             aStream nextPutAll:'&amp;'    "mapping needed for all"
-"/        ] ifFalse:[ eachChar == $> ifTrue:[
-"/            aStream nextPutAll:'&gt;'     "mapping needed for comments"
-"/        ] ifFalse:[ eachChar == $' ifTrue:[
-"/            aStream nextPutAll:'&apos;'   "mapping needed for attributes"
-"/        ] ifFalse:[ eachChar == $" ifTrue:[
-"/            aStream nextPutAll:'&quot;'   "mapping needed for attributes"
+        ] ifFalse:[ eachChar == $> ifTrue:[
+            aStream nextPutAll:'&gt;'     "mapping needed only for ]]>"
         ] ifFalse:[
             |codePoint|
             codePoint := eachChar codePoint.
             ((codePoint < 16r20 and:[codePoint ~~ 9 and:[codePoint ~~ 10 and:[codePoint ~~ 13]]])
-             or:[codePoint >= 16r7F]) ifTrue:[
-                aStream nextPutAll:'&#'.
-                codePoint printOn:aStream.
+             or:[codePoint >= 16r7F 
+                 and:[codePoint <= 16r9F 
+                      or:[codePoint > 16rFF] "for now, always make sure, that output is ISO-8859-1 compatible"]
+            ]) ifTrue:[
+                aStream nextPutAll:'&#x'.
+                codePoint printOn:aStream base:16.
                 aStream nextPut:$;.
-        ] ifFalse:[
-            aStream nextPut:eachChar
-        ]]]"/]]]
-    ].
-!
-
-printfWith:arg1 with:arg2 with:arg3 with:arg4 with:arg5
-    "Format and print the receiver with <argI> formatted in C style,
-     as specified in the Unix C-language manual page for printf(3).
-     Return the resulting string (i.e actually, this is more like an sprintf)."
-
-    ^ self printf:(Array with:arg1 with:arg2 with:arg3 with:arg4 with:arg5)
-
-    "
-     Transcript showCR:('%d %05x %08o %b' printfWith:123 with:234 with:345 with:123)
-    "
+            ] ifFalse:[
+                aStream nextPut:eachChar
+            ].
+        ]]]
+    ].
+
+    "
+     String streamContents:[:s|'< & >' printXmlTextQuotedOn:s]
+     String streamContents:[:s|'< & >',(Character value:7) printXmlTextQuotedOn:s]
+     String streamContents:[:s|'< & >',(Character value:129) printXmlTextQuotedOn:s]
+     String streamContents:[:s|'< & >',(Character value:1000) printXmlTextQuotedOn:s]
+    "
+
+    "Modified: / 30-08-2018 / 22:39:00 / Claus Gittinger"
+    "Modified: / 03-12-2018 / 15:21:18 / Stefan Vogel"
 !
 
 xmlQuotedPrintString
     "convert aString to a valid XML string
-     that can be used for attributes, text, comments an PIs
-     TODO: care for 16bit UNICODE string and escape chars ..."
-
-    ^ String streamContents:[:s|
-        self printXmlQuotedOn:s
-    ].
+     that can be used for attributes, text, comments and PIs.
+     Returns the reciever, if there is nothing to quote."
+
+    |possiblyQuotedString|
+
+    possiblyQuotedString :=
+        String streamContents:[:s|
+            self printXmlQuotedOn:s
+        ].
+    possiblyQuotedString = self ifTrue:[
+        ^ self
+    ].
+    ^ possiblyQuotedString
+
+    "Modified (comment): / 28-07-2018 / 11:11:51 / Claus Gittinger"
 ! !
 
-
 !CharacterArray methodsFor:'queries'!
 
 bitsPerCharacter
@@ -6206,6 +7209,8 @@
      'hello' bitsPerCharacter
      'hello' asText allBold bitsPerCharacter
     "
+
+    "Modified (comment): / 11-06-2020 / 17:50:06 / Stefan Vogel"
 !
 
 bytesPerCharacter
@@ -6263,8 +7268,124 @@
     "Created: / 25-03-2019 / 16:22:00 / Claus Gittinger"
 !
 
+camelCaseSeparatedWordsDo:aBlock
+    |state newState in out ch part|
+
+    in := self readStream.
+    out := '' writeStream.
+    [in atEnd] whileFalse:[
+        ch := in next.
+        (ch isDigit or:[ch == $_]) ifFalse:[
+            newState := ch isUppercase.
+        ].
+        (newState ~~ state) ifTrue:[
+            newState == true ifTrue:[
+                "/ going from lower- to uppercase
+                part := out contents.
+                part notEmpty ifTrue:[ aBlock value:part ].
+                out :=  '' writeStream.
+                out nextPut:ch.
+                state := newState.
+            ] ifFalse:[
+                "/ going upper- to lowercase
+                out size <= 1 ifTrue:[
+                    out nextPut:ch.
+                ] ifFalse:[
+                    |prev|
+
+                    prev := out contents.
+                    aBlock value:(prev copyButLast).
+                    out := '' writeStream.
+                    out nextPut:prev last.
+                    out nextPut:ch.
+                ].    
+                state := newState.
+            ].    
+        ] ifFalse:[
+            out nextPut:ch.
+        ].    
+    ].
+    part := out contents.
+    part notEmpty ifTrue:[ aBlock value:part ].
+
+    "
+     'HelloWorld' camelCaseSeparatedWordsDo:[:w | Transcript showCR:w]
+     'abcDef'     camelCaseSeparatedWordsDo:[:w | Transcript showCR:w]
+     'UTFEncoder' camelCaseSeparatedWordsDo:[:w | Transcript showCR:w]
+     'JisEncoder' camelCaseSeparatedWordsDo:[:w | Transcript showCR:w]
+     'JISEncode'  camelCaseSeparatedWordsDo:[:w | Transcript showCR:w]
+    "
+!
+
+characterSize
+    "answer the size in bits of my largest character (actually only 7, 8, 16 or 32)"
+
+    |string max
+     sz "{ Class:SmallInteger}" |
+
+    (string := self string) ~~ self ifTrue:[
+        ^ 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.
+            ].
+        ].
+    ].
+
+    ^ max.
+
+    "
+     'hello' characterSize
+     'hello' asUnicode32String characterSize
+     'helloü' asUnicode32String characterSize
+     'hello' asText allBold characterSize
+    "
+!
+
+contains8BitCharacters
+    <resource: #obsolete>
+
+    ^ self containsNon7BitAscii
+!
+
+containsNon7BitAscii
+    "return true, if the underlying string contains 8BitCharacters (or widers)
+     (i.e. if it is non-ascii)"
+
+    |string
+     sz "{ Class:SmallInteger }"|
+
+    (string := self string) ~~ self ifTrue:[
+        ^ string containsNon7BitAscii
+    ].
+    sz := self size.
+    1 to:sz do:[:idx|
+        (self at:idx) codePoint > 16r7F ifTrue:[
+            ^ true.
+        ].
+    ].
+    ^ false.
+
+    "
+     'hello' asUnicode32String containsNon7BitAscii
+     'hello üöä' asUnicode32String containsNon7BitAscii
+     'hello' asUnicode32String asText allBold containsNon7BitAscii
+     'hello üö' asUnicode32String asText allBold containsNon7BitAscii
+    "
+!
+
 containsNon8BitElements
-    "return true, if the underlying string contains elements larger than a single byte"
+    "return true, if the receiver contains elements larger than a single byte"
 
     |string sz "{ Class:SmallInteger }"|
 
@@ -6282,14 +7403,18 @@
 
 continuesWith:aString startingAt:startIndex
     "return true, if the receiver beginning at startIndex
-     contains the characters in aString."
+     contains the characters in aString.
+     Returns false if the search reaches the end of the receiver 
+     before all characters have been compared."
 
     |sz  "{Class: SmallInteger }"
      idx "{Class: SmallInteger }"|
 
     sz := aString size.
+    (startIndex + sz - 1) > self size ifTrue:[^ false].
+
     idx := startIndex.
-
+    
     1 to:sz do:[:i |
         (self at:idx) ~~ (aString at:i) ifTrue:[^ false].
         idx := idx + 1
@@ -6299,6 +7424,8 @@
     "
      'hello world' continuesWith:'world' startingAt:6
      'hello world' continuesWith:'world' startingAt:7
+     'hello' continuesWith:'llo' startingAt:3
+     'hello' continuesWith:'llow' startingAt:3
     "
 
     "Created: 12.5.1996 / 15:46:40 / cg"
@@ -6347,7 +7474,10 @@
      and that singleByteStrings are therefore both unicode AND
      8859-1 encoded."
 
-    ^ #unicode
+    ^ #'iso10646-1'.
+    "/ ^ #unicode
+
+    "Modified: / 22-08-2018 / 09:30:16 / Claus Gittinger"
 !
 
 hasChangeOfEmphasis
@@ -6384,6 +7514,42 @@
     "Modified: 12.5.1996 / 20:32:05 / cg"
 !
 
+isInfix
+    "return true, if the receiver is a binary message selector"
+
+    ^ self first isLetterOrDigit not
+
+    "
+     #at:put: isInfix
+     #at: isInfix
+     #+ isInfix
+     #size isInfix
+    "
+
+    "Created: / 1.11.1997 / 12:34:55 / cg"
+    "Modified: / 1.11.1997 / 12:36:37 / cg"
+!
+
+isKeyword
+    "return true, if the receiver is a keyword message selector.
+     This is a quick check, which only looks at the last character.
+     Should only be used, if we already know that the receiver forms a valid selector.
+     To check an arbitrary string, use isKeywordSelector.
+     Bad naming, but compatibility is asking for it."
+
+    ^ self last == $:
+
+    "
+     #at:put: isKeyword
+     #at: isKeyword
+     #+ isKeyword
+     #size isKeyword
+    "
+
+    "Created: / 01-11-1997 / 12:34:55 / cg"
+    "Modified (comment): / 30-04-2016 / 18:19:11 / cg"
+!
+
 isLowercaseFirst
     "return true, if the first character is a lowercase character."
 
@@ -6395,6 +7561,26 @@
     "
 !
 
+isNumeric
+    "return true, if the receiver is some numeric word;
+     i.e. consists only of digits."
+
+    self size == 0 ifTrue:[
+        ^ false
+    ].
+    ^ self conform:[:char | char isDigit]
+
+    "
+     'helloWorld' isNumeric
+     'foo1234' isNumeric
+     'f1234' isNumeric
+     '1234' isNumeric
+     '+' isNumeric
+    "
+
+    "Modified: / 13-10-2006 / 12:54:12 / cg"
+!
+
 isUppercaseFirst
     "return true, if the first character is an uppercase character."
 
@@ -6406,6 +7592,23 @@
     "
 !
 
+isWhitespace
+    "return true, if the receiver is empty or contains only whitespace."
+
+    ^ (self indexOfNonSeparatorStartingAt:1) == 0
+
+    "
+     '' isWhitespace
+     '   ' isWhitespace
+     '   \    \' withCRs isWhitespace
+     '   a\    \' withCRs isWhitespace
+     '   \    \a' withCRs isWhitespace
+     'a   \    \a' withCRs isWhitespace
+    "
+
+    "Created: / 01-03-2017 / 15:24:53 / cg"
+!
+
 keywords
     "assuming the receiver is a keyword message selector,
      return the individual keywords (i.e. break it up at colons)
@@ -6440,18 +7643,15 @@
 !
 
 leftIndent
-    "if the receiver starts with spaces, return the number of spaces
+    "if the receiver starts with whiteSpace, return the number of whiteSpace chars
      at the left - otherwise, return 0.
-     If the receiver consists of spaces only, return the receiver's size."
-
-    |index "{Class: SmallInteger }"
-     end   "{Class: SmallInteger }"|
-
-    index := 1.
+     If the receiver consists of whiteSpace only, return the receiver's size."
+
+    |end   "{Class: SmallInteger }"|
+
     end := self size.
-    [index <= end] whileTrue:[
-        (self at:index) isSeparator ifFalse:[^ index - 1].
-        index := index + 1
+    1 to:end do:[:idx|
+        (self at:idx) isSeparator ifFalse:[^ idx - 1].
     ].
     ^ end
 
@@ -6459,9 +7659,12 @@
      '    hello' leftIndent
      'foo      ' leftIndent
      '         ' leftIndent
-    "
-
-    "Modified: 20.4.1996 / 19:28:43 / cg"
+     ((Character tab),(Character tab),'foo') leftIndent
+    "
+
+    "Modified: / 20-04-1996 / 19:28:43 / cg"
+    "Modified (comment): / 05-02-2019 / 11:22:57 / Claus Gittinger"
+    "Modified: / 11-06-2020 / 18:59:06 / Stefan Vogel"
 !
 
 nameSpaceSelectorParts
@@ -6496,6 +7699,47 @@
     "Modified: / 06-03-2007 / 11:51:15 / cg"
 !
 
+numArgs
+    <resource: #obsolete>
+    "treating the receiver as a message selector, return how many arguments would it take.
+     Please use argumentCount for ANSI compatibility."
+
+    ^ self argumentCount
+!
+
+partsIfSelector
+    "treat the receiver as a message selector, return a collection of parts.
+     Notice: this is more tolerant than Smalltalk's syntax would suggest;
+     especially it allows for empty keyword parts between colons.
+     This is not (and should not be checked here), to allow parsing of
+     degenerate selectors as appearing with objectiveC."
+
+    |idx1 "{ Class: SmallInteger }"
+     coll idx2 sz|
+
+    coll := OrderedCollection new.
+    idx1 := 1.
+    sz := self size.
+    [
+        idx2 := self indexOf:$: startingAt:idx1.
+        (idx2 == 0 or:[idx2 == sz]) ifTrue:[
+            coll add:(self copyFrom:idx1).
+            ^ coll
+        ].
+        coll add:(self copyFrom:idx1 to:idx2).
+        idx1 := idx2 + 1
+    ] loop.
+
+    "
+     'foo:' partsIfSelector
+     'foo:bar:' partsIfSelector
+     'foo::::' partsIfSelector
+     #foo:bar: partsIfSelector
+     'hello' partsIfSelector
+     '+' partsIfSelector
+    "
+!
+
 speciesForSubcollection
     "answer the class, when splitting instances into subcollections"
 
@@ -6560,10 +7804,73 @@
     "Modified: / 18.7.1998 / 22:53:02 / cg"
 !
 
+expandNumericPlaceholdersWith:argArrayOrDictionary
+    "return a copy of the receiver, where all %i escapes with numeric keys are
+     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'.
+
+     This will ignore all non-numeric keys (and leave them as is)."
+
+    |stream|
+
+    stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
+    "/ self expandPlaceholdersWith:argArrayOrDictionary on:stream.
+    self 
+        expandPlaceholders:$% with:argArrayOrDictionary 
+        ignoreNumericEscapes:false 
+        ignoreNonNumericEscapes:true
+        ignoreSpecialEscapes:true
+        requireParentheses:true
+        ifKeyAbsent:nil
+        on:stream.
+    ^ stream contents.
+
+    "
+     'hello %1' expandNumericPlaceholdersWith:#('world')          
+     'hello %(1)' expandNumericPlaceholdersWith:#('world')          
+     'hello %(10)' expandNumericPlaceholdersWith:#('world')          
+     'hello %1 %abc' expandNumericPlaceholdersWith:#('world')          
+     'hello %1 %(abc)' expandNumericPlaceholdersWith:#('world')          
+    "
+
+    "
+     'hello %1' expandPlaceholdersWith:#('world')          
+     'hello %1 %abc' expandNumericPlaceholdersWith:#('world' 'nononono')          
+     'hello %1 %abc' expandPlaceholdersWith:#('world' 'nononono')          
+     'hello %1 %(abc)' expandNumericPlaceholdersWith:#('world' 'nononono')          
+     'hello %1 %(abc)' expandPlaceholdersWith:#('world' 'nononono')          
+    "
+
+    "Modified: / 01-07-1997 / 00:53:24 / cg"
+    "Modified: / 14-07-2018 / 09:23:31 / Claus Gittinger"
+    "Modified (comment): / 09-09-2019 / 13:58:20 / Stefan Vogel"
+!
+
+expandPlaceholders
+    "return a copy of the receiver, where %<special> escapes are expanded.
+     %<..>
+        Insert a character constant or character sequence, being one of:
+            cr nl tab return lf crlf ff null backspace bell esc newPage space
+        i.e. you can use %<cr> to insert a CR, and %<tab> to insert a TAB.
+
+     See also bindWith:... for VisualAge compatibility."
+
+    ^ self expandPlaceholdersWith:nil
+
+    "
+     'hello a%<crlf>b' expandPlaceholders
+    "
+
+    "Modified: / 01-07-1997 / 00:53:24 / cg"
+    "Modified: / 14-07-2018 / 09:23:31 / Claus Gittinger"
+!
+
 expandPlaceholders:escapeCharacter with:argArrayOrDictionary
-    "this is the generic version of the old %-escaping method, allowing for an arbitrary
+    "this is a more general version of the old %-escaping method, allowing for an arbitrary
      escape character to be used (typically $$ or $% are effectively used).
-     Return a copy of the receiver, where all %i escapes are
+
+     Returns a copy of the receiver, where all %i escapes are
      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'.
@@ -6572,19 +7879,26 @@
      In this case, %a .. %z and %(...) are also allowed.
      (%1..%9 require a numeric key in the dictionary, however)
      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).
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
      See also bindWith:... for VisualAge compatibility."
 
     |stream|
 
     stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
-    self expandPlaceholders:escapeCharacter with:argArrayOrDictionary on:stream.
+    self expandPlaceholders:escapeCharacter with:argArrayOrDictionary 
+         ignoreNumericEscapes:false 
+         ignoreNonNumericEscapes:false
+         ignoreSpecialEscapes:false
+         requireParentheses:true 
+         ifKeyAbsent:nil
+         on:stream.
     ^ stream contents.
 
-
     "
      'hello %1' expandPlaceholdersWith:#('world')
+     'hello %1' expandPlaceholders:$% with:#('world')  
+     'hello %1' expandPlaceholders:$$ with:#('world')  
+     'hello $1' expandPlaceholders:$$ with:#('world')  
      'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this')
      'hello %2; how is %1' expandPlaceholdersWith:#('world' 'this')
      '%1 plus %2 gives %3 ' expandPlaceholdersWith:#(4 5 9)
@@ -6608,7 +7922,862 @@
      'hello $1 %a $b %(foo) $foo ' expandPlaceholders:$% with:dict.
     "
 
-    "Modified: 1.7.1997 / 00:53:24 / cg"
+    "Modified: / 01-07-1997 / 00:53:24 / cg"
+    "Modified: / 14-06-2018 / 11:46:18 / Claus Gittinger"
+!
+
+expandPlaceholders:escapeCharacter with:argArrayOrDictionary 
+    ignoreNumericEscapes:ignoreNumericEscapes 
+    ignoreNonNumericEscapes:ignoreNonNumericEscapes
+    ignoreSpecialEscapes:ignoreSpecialEscapes
+    requireParentheses:requireParentheses
+    "this is the generic version of the old %-escaping method, allowing for an arbitrary
+     escape character to be used (typically $$ or $% are effectively used).
+
+     Return a copy of the receiver, where all %i escapes are
+     replaced by corresponding arguments' printStrings from the argArray.
+     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, values in argArrayOrDictionary may be blocks.
+
+     To get a '%' character, use a '%%'-escape.
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
+
+     See also bindWith:... for VisualAge compatibility.
+     Use %<cr> to insert a CR and %<tab> to insert a TAB.
+
+     ignoreNumericEscapes controls if %<nr> escapes are expanded or not.
+     This is required for Windows batch-script expansion, where %<nr> should be left unchanged.
+
+     requireParentheses controls if $abc is allowed or not.
+     If true, multi-character replacements need to be parenthized as $(abc);
+     if false, you can also write $abc.
+    "
+
+    |stream|
+
+    stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
+    self 
+        expandPlaceholders:escapeCharacter with:argArrayOrDictionary 
+        ignoreNumericEscapes:ignoreNumericEscapes 
+        ignoreNonNumericEscapes:ignoreNonNumericEscapes
+        ignoreSpecialEscapes:ignoreSpecialEscapes
+        requireParentheses:requireParentheses 
+        ifKeyAbsent:nil
+        on:stream.
+    ^ stream contents
+
+    "
+     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
+     'hello %a%<cr>' expandPlaceholders:$% 
+                    with:(Dictionary new at:'a' put:'world';yourself) 
+                    on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
+     'hello %(aa)%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) ignoreNumericEscapes:true requireParentheses:false on:Transcript.
+
+     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.
+     ]
+    "
+
+    "without xlation dictionary:
+        'hello %1' expandPlaceholdersWith:nil.
+        'hello%<cr> %1' expandPlaceholdersWith:nil.
+    "
+
+    "
+     |dict|
+
+     dict := Dictionary new.
+     dict at:1 put:'one'.
+     dict at:$a put:'AAAAA'.
+     dict at:$b put:[ Time now ].
+     String streamContents:[:s|
+         'hello $1 $a $b' expandPlaceholders:$$ with:dict on:s.
+     ].
+    "
+
+    "using blocks:
+     |dict|
+
+     dict := Dictionary new.
+     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.
+     ].
+    "
+
+    "Created: / 14-01-2019 / 17:43:03 / Claus Gittinger"
+    "Modified: / 05-06-2019 / 17:05:47 / Claus Gittinger"
+!
+
+expandPlaceholders:escapeCharacter with:argArrayOrDictionary 
+    ignoreNumericEscapes:ignoreNumericEscapes 
+    ignoreNonNumericEscapes:ignoreNonNumericEscapes
+    ignoreSpecialEscapes:ignoreSpecialEscapes
+    requireParentheses:requireParentheses
+    ifKeyAbsent:ifKeyAbsentBlockOrNil
+
+    "this is the generic version of the old %-escaping method, allowing for an arbitrary
+     escape character to be used (typically $$ or $% are effectively used).
+
+     Return a copy of the receiver, where all %i escapes are
+     replaced by corresponding arguments' printStrings from the argArray.
+     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, values in argArrayOrDictionary may be blocks.
+
+     To get a '%' character, use a '%%'-escape.
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
+
+     See also bindWith:... for VisualAge compatibility.
+     Use %<cr> to insert a CR and %<tab> to insert a TAB.
+
+     ignoreNumericEscapes controls if %<nr> escapes are expanded or not.
+     This is required for Windows batch-script expansion, where %<nr> should be left unchanged.
+
+     requireParentheses controls if $abc is allowed or not.
+     If true, multi-character replacements need to be parenthized as $(abc);
+     if false, you can also write $abc.
+    "
+
+    |stream|
+
+    stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
+    self 
+        expandPlaceholders:escapeCharacter with:argArrayOrDictionary 
+        ignoreNumericEscapes:ignoreNumericEscapes 
+        ignoreNonNumericEscapes:ignoreNonNumericEscapes
+        ignoreSpecialEscapes:ignoreSpecialEscapes
+        requireParentheses:requireParentheses 
+        ifKeyAbsent:ifKeyAbsentBlockOrNil
+        on:stream.
+    ^ stream contents
+
+    "
+     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
+     'hello %a%<cr>' expandPlaceholders:$% 
+                    with:(Dictionary new at:'a' put:'world';yourself) 
+                    on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
+     'hello %(aa)%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) ignoreNumericEscapes:true requireParentheses:false on:Transcript.
+
+     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.
+     ]
+    "
+
+    "without xlation dictionary:
+        'hello %1' expandPlaceholdersWith:nil.
+        'hello%<cr> %1' expandPlaceholdersWith:nil.
+    "
+
+    "
+     |dict|
+
+     dict := Dictionary new.
+     dict at:1 put:'one'.
+     dict at:$a put:'AAAAA'.
+     dict at:$b put:[ Time now ].
+     String streamContents:[:s|
+         'hello $1 $a $b' expandPlaceholders:$$ with:dict on:s.
+     ].
+    "
+
+    "using blocks:
+     |dict|
+
+     dict := Dictionary new.
+     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.
+     ].
+    "
+
+    "Created: / 14-01-2019 / 17:43:03 / Claus Gittinger"
+    "Modified: / 05-06-2019 / 17:05:47 / Claus Gittinger"
+!
+
+expandPlaceholders:escapeCharacter with:argArrayOrDictionary 
+    ignoreNumericEscapes:ignoreNumericEscapes 
+    ignoreNonNumericEscapes:ignoreNonNumericEscapes
+    ignoreSpecialEscapes:ignoreSpecialEscapes
+    requireParentheses:requireParentheses
+    ifKeyAbsent:replaceActionOrNil
+    on:aStream
+
+    "this is the central method for %-escaping, allowing for an arbitrary
+     escape character to be used (typically $$ or $% are effectively used).
+
+     Write the receiver to aStream, where all %i escapes are
+     replaced by corresponding arguments' printStrings from the argArray.
+     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, values in argArrayOrDictionary may be blocks.
+
+     To get a '%' character, use a '%%'-escape.
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
+
+     See also bindWith:... for VisualAge compatibility.
+
+     - %<..>
+        Insert a character constant or character sequence, being one of:
+            cr nl tab return lf crlf ff null backspace bell esc newPage space
+        i.e. you can use %<cr> to insert a CR, and %<tab> to insert a TAB.
+        controlled by ignoreSpecialEscapes
+
+     - ignoreNumericEscapes 
+        controls if %<nr> escapes are expanded or not.
+        This is required for Windows batch-script expansion, where %<nr> should be left unchanged.
+
+     - ignoreSpecialEscapes 
+        controls if control characters like %<cr> are expanded or not.
+
+     - requireParentheses 
+        controls if $abc is allowed or not.
+        If true, multi-character replacements need to be parenthized as $(abc),
+                and $abc is interpreted as $(a)bc
+        If false, you can also write $abc.
+
+     - keepIfNoSuchKey 
+        controls what should happen if a variable/index is encountered which is not found in argArrayOrDictionary. 
+        It can be nil or a two arg block.
+        If nil, the sequence is replaced by an empty string (i.e. 'abc$(foo)def' -> 'abcdef')
+        if aBlock, it will be called with both the full escape sequence and the cariable only as arguments,
+        and the expansion will be what the block returns. 
+        i.e. if the block is [:meta :name | meta], then the above will result in 'abc$(foo)def'
+        and if the block is [:meta :name | name], then the above will result in 'abcfoodef'
+        Useful if you want to expand a string twice, without loosing the key-sequences in the first place.
+        Notice: for stupid backward compatibility, keepIfNoSuchKey is not applied for %X sequences, where X is a single letter.
+    "
+
+    |next v key numericKey
+     idx   "{ Class:SmallInteger }"
+     idx2  "{ Class:SmallInteger }"
+     qIdx  "{ Class:SmallInteger }"
+     start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }"
+     noReplacementAction default|
+
+    replaceActionOrNil isNil ifTrue:[
+        noReplacementAction := [:seq :var :default | (default ? '')]
+    ] ifFalse:[
+        noReplacementAction := replaceActionOrNil
+    ].
+
+    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 at idx"
+        idx > start ifTrue:[
+            aStream nextPutAll:self startingAt:start to:(idx - 1).
+        ].
+        next := self at:(idx + 1).
+        (next == escapeCharacter) ifTrue:[
+            "doubled escapeCharacter"
+            aStream nextPut:escapeCharacter.
+        ] ifFalse:[
+            "%<...> "
+            next == $< ifTrue:[
+                ignoreSpecialEscapes ifTrue:[
+                    aStream nextPut:escapeCharacter.
+                    aStream nextPut:next.
+                ] ifFalse:[
+                    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 backspace bell esc newPage space) includesIdentical:key) ifTrue:[
+                        aStream nextPut:(Character perform:key).
+                    ] ifFalse:[
+                        (key == #crlf) ifTrue:[
+                            aStream nextPutAll:(String crlf).
+                        ] ifFalse:[
+                            aStream nextPutAll:key.
+                        ]
+                    ].
+                ].
+            ] ifFalse:[
+                argArrayOrDictionary isNil ifTrue:[
+                    "/ %x but no dictionary provided (strange error case, actually)
+                    aStream nextPut:next.
+                ] ifFalse:[    
+                    (next isDigit and:[ignoreNumericEscapes not]) ifTrue:[
+                        "/ %N (N is digit)
+                        key := next asString.
+                        numericKey := next digitValue.
+                        (((idx + 2) <= self size) and:[(next := self at:idx+2) isDigit]) ifTrue:[
+                            key := key,next.
+                            idx := idx + 1.
+                            [((idx + 2) <= self size) and:[(next := self at:idx+2) isDigit]] whileTrue:[
+                                key := key,next.
+                                idx := idx + 1.
+                            ].
+                            numericKey := Integer readFrom:key.
+                        ].
+                        v := argArrayOrDictionary 
+                                at:numericKey 
+                                ifAbsent:[ noReplacementAction valueWithOptionalArgument:(escapeCharacter,key) and:key and:nil ].
+                    ] ifFalse:[
+                        next == $( ifTrue:[
+                            "/ %(name) 
+                            idx2 := self indexOf:$) startingAt:idx+2.
+                            idx2 > 0 ifFalse:[
+                                self assert:(idx2 > 0) message:'closing parenthesis missing'.
+                                self error:'closing parenthesis missing'.
+                            ].
+                            key := self copyFrom:idx+2 to:idx2-1.
+                            idx := idx2-1.
+
+                            (qIdx := key indexOf:$?) > 0 ifTrue:[
+                                default := key copyFrom:qIdx+1.
+                                key := key copyTo:qIdx-1.
+                            ].
+
+                            (key isNumeric 
+                              and:[(numericKey := Integer readFrom:key onError:nil) notNil])
+                            ifTrue:[
+                                ignoreNumericEscapes ifTrue:[
+                                    v := escapeCharacter,'(',key,')'
+                                ] ifFalse:[
+                                    v := argArrayOrDictionary 
+                                            at:numericKey 
+                                            ifAbsent:[ noReplacementAction valueWithOptionalArgument:(escapeCharacter,'(',key,')') and:key and:default ]
+                                ]
+                            ] ifFalse:[
+                                ignoreNonNumericEscapes ifTrue:[
+                                    v := escapeCharacter,'(',key,')'
+                                ] ifFalse:[
+                                    argArrayOrDictionary isBlock ifTrue:[
+                                        v := argArrayOrDictionary value:key
+                                    ] ifFalse:[    
+                                        (argArrayOrDictionary includesKey:key) ifTrue:[
+                                            v := argArrayOrDictionary at:key
+                                        ] ifFalse:[
+                                            key := key asSymbolIfInternedOrSelf.
+                                            (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:[
+                                                    v := noReplacementAction valueWithOptionalArgument:(escapeCharacter,'(',key,')') and:key and:default
+                                                ]
+                                            ].
+                                        ].
+                                    ].
+                                ].
+                            ].
+                        ] ifFalse:[
+                            (ignoreNonNumericEscapes not 
+                              and:[ next isLetter 
+                              and:[ argArrayOrDictionary isSequenceable not "is a Dictionary"]]
+                            ) ifTrue:[
+                                "%X (X is letter)"
+                                requireParentheses ifTrue:[
+                                    key := next.
+                                ] ifFalse:[
+                                    idx2 := self findFirst:[:ch | (ch isLetterOrDigitOrUnderline) not] startingAt:idx+2.
+                                    idx2 == 0 ifTrue:[idx2 := self size + 1].
+                                    key := self copyFrom:idx+1 to:idx2-1.
+                                    idx := idx2 - 2.
+                                ].
+
+                                argArrayOrDictionary isBlock ifTrue:[
+                                    v := argArrayOrDictionary value:key
+                                ] ifFalse:[        
+                                    v := argArrayOrDictionary
+                                            at:key
+                                            ifAbsent:[
+                                                "try symbol or string instead of character"
+                                                argArrayOrDictionary
+                                                    at:key asString asSymbolIfInternedOrSelf
+                                                    ifAbsent:[
+                                                        escapeCharacter asString , key
+                                                    ].
+                                         ].
+                                ].
+                            ] ifFalse:[
+                                v := String with:escapeCharacter with:next.
+                            ].
+                        ]
+                    ].
+
+                    v isBlock ifTrue:[
+                        v := v value
+                    ].
+                    v printOn:aStream.
+                ]
+            ].
+        ].
+        start := idx + 2
+    ].
+
+    "
+     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
+     'hello %a%<cr>' expandPlaceholders:$% 
+                    with:(Dictionary new at:'a' put:'world';yourself) 
+                    on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
+     'hello %(aa)%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) ignoreNumericEscapes:true requireParentheses:false on:Transcript.
+
+     'hello %10%9%8' expandPlaceholders:$% with:{ 'x1' . 'x2' . 'x3' . 'x4' . 'x5' . 'x6' . 'x7' . 'x8' . 'x9' . 'x10' }
+     'hello %10' expandPlaceholders:$% with:{ 'x1' . 'x2' . 'x3' . 'x4' . 'x5' . 'x6' . 'x7' . 'x8' . 'x9' . 'x10' }
+
+     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.
+     ]
+    "
+
+    "without xlation dictionary:
+        'hello %1' expandPlaceholdersWith:nil.
+        'hello%<cr> %1' expandPlaceholdersWith:nil.
+    "
+
+    "
+     |dict|
+
+     dict := Dictionary new.
+     dict at:1 put:'one'.
+     dict at:$a put:'AAAAA'.
+     dict at:$b put:[ Time now ].
+     String streamContents:[:s|
+         'hello $1 $a $b' expandPlaceholders:$$ with:dict on:s.
+     ].
+    "
+
+    "using blocks:
+     |dict|
+
+     dict := Dictionary new.
+     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.
+     ].
+    "
+
+    "Created: / 14-01-2019 / 17:43:03 / Claus Gittinger"
+    "Modified: / 05-06-2019 / 17:05:47 / Claus Gittinger"
+    "Modified: / 25-02-2020 / 15:41:48 / Stefan Reise"
+    "Modified: / 06-06-2020 / 15:18:57 / cg"
+    "Modified (comment): / 11-06-2020 / 17:33:53 / Stefan Vogel"
+!
+
+expandPlaceholders:escapeCharacter 
+    with:argArrayOrDictionary 
+    ignoreNumericEscapes:ignoreNumericEscapes 
+    ignoreNonNumericEscapes:ignoreNonNumericEscapes
+    ignoreSpecialEscapes:ignoreSpecialEscapes
+    requireParentheses:requireParentheses 
+    on:aStream
+
+    "this is the central method for %-escaping, allowing for an arbitrary
+     escape character to be used (typically $$ or $% are effectively used).
+
+     Write the receiver to aStream, where all %i escapes are
+     replaced by corresponding arguments' printStrings from the argArray.
+     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, values in argArrayOrDictionary may be blocks.
+
+     To get a '%' character, use a '%%'-escape.
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
+
+     See also bindWith:... for VisualAge compatibility.
+     Use %<cr> to insert a CR and %<tab> to insert a TAB.
+
+     ignoreNumericEscapes controls if %<nr> escapes are expanded or not.
+     This is required for Windows batch-script expansion, where %<nr> should be left unchanged.
+
+     ignoreSpecialEscapes controls if control characters like %<cr> are expanded or not.
+
+     requireParentheses controls if $abc is allowed or not.
+     If true, multi-character replacements need to be parenthized as $(abc) and the above is
+     interpreted as $(a)bc;
+     if false, you can also write $abc.
+    "
+
+    ^ self
+        expandPlaceholders:escapeCharacter 
+        with:argArrayOrDictionary 
+        ignoreNumericEscapes:ignoreNumericEscapes 
+        ignoreNonNumericEscapes:ignoreNonNumericEscapes
+        ignoreSpecialEscapes:ignoreSpecialEscapes
+        requireParentheses:requireParentheses 
+        ifKeyAbsent:nil
+        on:aStream
+!
+
+expandPlaceholders:escapeCharacter with:argArrayOrDictionary 
+    ignoreNumericEscapes:ignoreNumericEscapes 
+    on:aStream
+    "this is the generic version of the old %-escaping method, allowing for an arbitrary
+     escape character to be used (typically $$ or $% are effectively used).
+
+     Write the receiver to aStream, where all %i escapes are
+     replaced by corresponding arguments' printStrings from the argArray.
+     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, values in argArrayOrDictionary may be blocks.
+
+     To get a '%' character, use a '%%'-escape.
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
+
+     See also bindWith:... for VisualAge compatibility.
+     Use %<cr> to insert a CR and %<tab> to insert a TAB.
+
+     ignoreNumericEscapes controls if %<nr> escapes are expanded or not.
+     This is required for Windows batch-script expansion, where %<nr> should be left
+     unchanged."
+
+    ^ self
+        expandPlaceholders:escapeCharacter 
+        with:argArrayOrDictionary 
+        ignoreNumericEscapes:ignoreNumericEscapes 
+        ignoreNonNumericEscapes:false
+        ignoreSpecialEscapes:false
+        requireParentheses:true
+        ifKeyAbsent:nil
+        on:aStream
+
+    "
+     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.
+     ]
+    "
+
+    "without xlation dictionary:
+        'hello %1' expandPlaceholdersWith:nil.
+        'hello%<cr> %1' expandPlaceholdersWith:nil.
+    "
+
+    "
+     |dict|
+
+     dict := Dictionary new.
+     dict at:1 put:'one'.
+     dict at:$a put:'AAAAA'.
+     dict at:$b put:[ Time now ].
+     dict at:'foo' put:'FOO'.
+     dict at:'foo2' put:'FOO\BAR'.
+     String streamContents:[:s|
+         'hello $1 $a $b $(foo) $$(foo) $(foo2) ' expandPlaceholders:$$ with:dict on:s.
+     ].                                                    
+    "
+
+    "using blocks:
+     |dict|
+
+     dict := Dictionary new.
+     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.
+     ].
+    "
+
+    "Created: / 14-06-2018 / 11:44:08 / Claus Gittinger"
+    "Modified (comment): / 14-01-2019 / 17:44:02 / Claus Gittinger"
+!
+
+expandPlaceholders:escapeCharacter 
+    with:argArrayOrDictionary 
+    ignoreNumericEscapes:ignoreNumericEscapes 
+    requireParentheses:requireParentheses
+
+    "this is a more general version of the old %-escaping method, allowing for an arbitrary
+     escape character to be used (typically $$ or $% are effectively used).
+     See also bindWith:... for VisualAge compatibility.
+
+     - ignoreNumericEscapes 
+        controls if %<nr> escapes are expanded or not.
+        This is required for Windows batch-script expansion, where %<nr> should be left unchanged.
+
+     - requireParentheses 
+        controls if $abc is allowed or not.
+        If true, multi-character replacements need to be parenthized as $(abc);
+        if false, you can also write $abc.
+    "
+
+    |stream|
+
+    stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
+    self 
+        expandPlaceholders:escapeCharacter 
+        with:argArrayOrDictionary 
+        ignoreNumericEscapes:ignoreNumericEscapes 
+        ignoreNonNumericEscapes:false
+        ignoreSpecialEscapes:false
+        requireParentheses:requireParentheses 
+        ifKeyAbsent:nil
+        on:stream.
+    ^ stream contents
+
+    "
+     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
+     'hello %a%<cr>' expandPlaceholders:$% 
+                    with:(Dictionary new at:'a' put:'world';yourself) 
+                    on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
+     'hello %(aa)%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) ignoreNumericEscapes:true requireParentheses:false on:Transcript.
+
+     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.
+     ]
+    "
+
+    "without xlation dictionary:
+        'hello %1' expandPlaceholdersWith:nil.
+        'hello%<cr> %1' expandPlaceholdersWith:nil.
+    "
+
+    "
+     |dict|
+
+     dict := Dictionary new.
+     dict at:1 put:'one'.
+     dict at:$a put:'AAAAA'.
+     dict at:$b put:[ Time now ].
+     String streamContents:[:s|
+         'hello $1 $a $b' expandPlaceholders:$$ with:dict on:s.
+     ].
+    "
+
+    "using blocks:
+     |dict|
+
+     dict := Dictionary new.
+     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.
+     ].
+    "
+
+    "Created: / 14-01-2019 / 17:43:03 / Claus Gittinger"
+    "Modified: / 05-06-2019 / 17:05:47 / Claus Gittinger"
+!
+
+expandPlaceholders:escapeCharacter with:argArrayOrDictionary 
+    ignoreNumericEscapes:ignoreNumericEscapes 
+    requireParentheses:requireParentheses 
+    on:aStream
+
+    "this is the generic version of the old %-escaping method, allowing for an arbitrary
+     escape character to be used (typically $$ or $% are effectively used).
+
+     Write the receiver to aStream, where all %i escapes are
+     replaced by corresponding arguments' printStrings from the argArray.
+     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, values in argArrayOrDictionary may be blocks.
+
+     To get a '%' character, use a '%%'-escape.
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
+
+     See also bindWith:... for VisualAge compatibility.
+     Use %<cr> to insert a CR and %<tab> to insert a TAB.
+
+     ignoreNumericEscapes controls if %<nr> escapes are expanded or not.
+     This is required for Windows batch-script expansion, where %<nr> should be left unchanged.
+
+     requireParentheses controls if $abc is allowed or not.
+     If true, multi-character replacements need to be parenthized as $(abc);
+     if false, you can also write $abc.
+    "
+
+    self 
+        expandPlaceholders:escapeCharacter 
+        with:argArrayOrDictionary 
+        ignoreNumericEscapes:ignoreNumericEscapes 
+        ignoreNonNumericEscapes:false
+        ignoreSpecialEscapes:false
+        requireParentheses:requireParentheses 
+        ifKeyAbsent:nil
+        on:aStream.
+
+    "
+     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
+     'hello %a%<cr>' expandPlaceholders:$% 
+                    with:(Dictionary new at:'a' put:'world';yourself) 
+                    on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
+     'hello %(aa)%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
+     'hello %aa%<cr>' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) ignoreNumericEscapes:true requireParentheses:false on:Transcript.
+
+     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.
+     ]
+    "
+
+    "without xlation dictionary:
+        'hello %1' expandPlaceholdersWith:nil.
+        'hello%<cr> %1' expandPlaceholdersWith:nil.
+    "
+
+    "
+     |dict|
+
+     dict := Dictionary new.
+     dict at:1 put:'one'.
+     dict at:$a put:'AAAAA'.
+     dict at:$b put:[ Time now ].
+     String streamContents:[:s|
+         'hello $1 $a $b' expandPlaceholders:$$ with:dict on:s.
+     ].
+    "
+
+    "using blocks:
+     |dict|
+
+     dict := Dictionary new.
+     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.
+     ].
+    "
+
+    "Created: / 14-01-2019 / 17:43:03 / Claus Gittinger"
+    "Modified: / 05-06-2019 / 17:05:47 / Claus Gittinger"
 !
 
 expandPlaceholders:escapeCharacter with:argArrayOrDictionary on:aStream
@@ -6626,94 +8795,24 @@
      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).
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
 
      See also bindWith:... for VisualAge compatibility.
      Use %<cr> to insert a CR and %<tab> to insert a TAB."
 
-    |next v key
-     idx   "{ SmallInteger }"
-     idx2  "{ SmallInteger }"
-     start "{ SmallInteger }"
-     stop  "{ SmallInteger }"|
-
-    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 asSymbolIfInternedOrSelf.
-                            (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 or string instead of character"
-                                        argArrayOrDictionary
-                                            at:next asString asSymbolIfInternedOrSelf
-                                            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
-    ].
-
-    "
+    ^ self
+        expandPlaceholders:escapeCharacter 
+        with:argArrayOrDictionary 
+        ignoreNumericEscapes:false 
+        ignoreNonNumericEscapes:false 
+        ignoreSpecialEscapes:false 
+        requireParentheses:true
+        ifKeyAbsent:nil
+        on:aStream
+
+    "
+     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
+
      String streamContents:[:s|
         'hello %1' expandPlaceholders:$% with:#('world') on:s.
         s cr.
@@ -6759,6 +8858,7 @@
     "
 
     "Modified: / 18-11-2010 / 15:43:28 / cg"
+    "Modified (comment): / 14-01-2019 / 18:02:59 / Claus Gittinger"
 !
 
 expandPlaceholdersWith:argArrayOrDictionary
@@ -6774,14 +8874,21 @@
      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).
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
      See also bindWith:... for VisualAge compatibility."
 
     |stream|
 
     stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
-    self expandPlaceholdersWith:argArrayOrDictionary on:stream.
+    "/ self expandPlaceholdersWith:argArrayOrDictionary on:stream.
+    self 
+        expandPlaceholders:$% with:argArrayOrDictionary 
+        ignoreNumericEscapes:false 
+        ignoreNonNumericEscapes:false
+        ignoreSpecialEscapes:false
+        requireParentheses:true
+        ifKeyAbsent:nil
+        on:stream.
     ^ stream contents.
 
     "
@@ -6812,7 +8919,40 @@
      'hello %1 %a %b %(foo)' expandPlaceholdersWith:dict
     "
 
-    "Modified: 1.7.1997 / 00:53:24 / cg"
+    "Modified: / 01-07-1997 / 00:53:24 / cg"
+    "Modified: / 14-07-2018 / 09:23:31 / Claus Gittinger"
+!
+
+expandPlaceholdersWith:argArrayOrDictionary ifKeyAbsent:ifNoSuchKeyActionOrNil
+    "return a copy of the receiver, where all %i escapes are
+     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'.
+     The argument may also be a dictionary, providing values for symbolic keys.
+     To get a '%' character, use a '%%'-escape.
+
+     See the comment in
+        expandPlaceholders:with:ignoreNumericEscapes:ignoreNonNumericEscapes:ignoreSpecialEscapes:requireParentheses:ifKeyAbsent:on:
+     for a full explanation.
+
+     See also bindWith:... for VisualAge compatibility."
+
+    |stream|
+
+    stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
+    self 
+        expandPlaceholders:$% with:argArrayOrDictionary 
+        ignoreNumericEscapes:false 
+        ignoreNonNumericEscapes:false
+        ignoreSpecialEscapes:false
+        requireParentheses:true
+        ifKeyAbsent:ifNoSuchKeyActionOrNil
+        on:stream.
+    ^ stream contents.
+
+    "
+     'hello %(abc) %1 %a %; %%' expandPlaceholdersWith:nil ifNoSuchKey:[:str :nm | str]
+    "
 !
 
 expandPlaceholdersWith:argArrayOrDictionary on:aStream
@@ -6828,13 +8968,19 @@
      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).
+     To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
 
      See also bindWith:... for VisualAge compatibility.
      Use %<cr> to insert a CR and %<tab> to insert a TAB."
 
-    ^ self expandPlaceholders:$% with:argArrayOrDictionary on:aStream
+    ^ self 
+        expandPlaceholders:$% with:argArrayOrDictionary 
+        ignoreNumericEscapes:false 
+        ignoreNonNumericEscapes:false
+        ignoreSpecialEscapes:false
+        requireParentheses:true
+        ifKeyAbsent:nil
+        on:aStream
 
     "
      String streamContents:[:s|
@@ -6869,6 +9015,34 @@
     "
 
     "Modified: / 18-11-2010 / 15:43:28 / cg"
+    "Modified: / 14-06-2018 / 11:45:36 / Claus Gittinger"
+!
+
+extractPlaceHolders:escapeCharacter
+    "returns a list of placeholder keys of the form %i,
+     where i is either a single digit (as in %1, %2)
+     or a single letter (as in %a, %z)
+     or a word-key, as in %(one), %(fooBar).
+     For numeric keys, the returned collection contains integers;
+     for non-numeric ones, it includes strings."
+
+    |setOfKeys loggingDictionary|
+
+    setOfKeys := Set new.
+    loggingDictionary := Plug new.
+    loggingDictionary respondTo:#at: with:[:key | setOfKeys add:key. key asString].
+    loggingDictionary respondTo:#at:ifAbsent: with:[:key :def | setOfKeys add:key. key asString].
+    loggingDictionary respondTo:#includesKey: with:[:key | setOfKeys add:key. true].
+    loggingDictionary respondTo:#isSequenceable with:[false].
+    self expandPlaceholders:escapeCharacter with:loggingDictionary.
+    ^ setOfKeys
+    
+    "
+     self assert:('hello %1 and %2' extractPlaceHolders:$%) asSet = #(1 2) asSet
+     self assert:('hello %9 and %(10)' extractPlaceHolders:$%) asSet = #(9 10) asSet
+     self assert:('hello %a and %(foo) and %1' extractPlaceHolders:$%) asSet = #(1 'a' 'foo') asSet
+     self assert:('hello %a and %(foo) and %1' extractPlaceHolders:$$) asSet = #() asSet
+    "
 !
 
 firstLine
@@ -6905,7 +9079,7 @@
      The following escapes are generated:
         \'      single quote character
         \dQuote double quote character
-        \r      return character
+        \b      backspace character
         \r      return character
         \n      newline character
         \t      tab character
@@ -6919,7 +9093,7 @@
            but it cannot be changed easily, as these methods are already used heavily
     "
 
-    |anyEscapeNeeded out seq|
+    |anyEscapeNeeded out|
 
     "
      first, check if any escape is needed and return the receiver unchanged if not
@@ -6927,57 +9101,26 @@
     anyEscapeNeeded := self
                         contains:[:ch |
                             ((ch codePoint between:32 and:126) not
-                            or:[ch == $' or:[ch == $"]])
+                            or:[ch == $' or:[ch == $" or:[ch == $\]]])
                         ].
     anyEscapeNeeded ifFalse:[ ^ self ].
 
     self hasChangeOfEmphasis ifTrue:[ self error:'emphasis not supported' ].
 
     out := WriteStream on:(String uninitializedNew:self size-1).
-
-    self do:[:ch |
-        |cp|
-
-        (ch == $' or:[ch == $"]) ifTrue:[
-            out nextPut:$\.
-            out nextPut:ch.
-        ] ifFalse:[
-            (ch codePoint between:32 and:126) ifTrue:[
-                out nextPut:ch
-            ] ifFalse:[
-                ch == Character return ifTrue:[
-                    seq := '\r'
-                ] ifFalse:[ ch == Character nl ifTrue:[
-                    seq := '\n'
-                ] ifFalse:[ ch == Character tab ifTrue:[
-                    seq := '\t'
-                ] ifFalse:[ ch == $\ ifTrue:[
-                    seq := '\\'
-                ] ifFalse:[
-                    cp := ch codePoint.
-                    cp <= 16rFF ifTrue:[
-                        seq := '\x' , (cp printStringRadix:16 padTo:2)
-                    ] ifFalse:[
-                        cp <= 16rFFFF ifTrue:[
-                            seq := '\u' , (cp printStringRadix:16 padTo:4)
-                        ] ifFalse:[
-                            seq := '\U',(cp printStringRadix:16 padTo:8)
-                        ]
-                    ]
-                ]]]].
-                out nextPutAll:seq
-            ].
-        ].
-    ].
+    self printWithCEscapesOn:out.
     ^ out contents
 
     "
-     'hello\n\tworld' withoutCEscapes.
+     'c:\foo\bar\baz' withCEscapes.  
+     c'hello\n\tworld' withCEscapes.
+     'hello\b\tworld' withoutCEscapes withCEscapes.
      'hello\nworld\na\n\tnice\n\t\tstring' withoutCEscapes withCEscapes.
      ('hello ',(Character value:16r1234),' world') withCEscapes
     "
 
     "Created: / 25-01-2012 / 11:08:16 / cg"
+    "Modified: / 12-11-2017 / 12:39:57 / cg"
 !
 
 withCRs
@@ -6994,6 +9137,17 @@
     "Modified: / 18.7.1998 / 22:53:02 / cg"
 !
 
+withDoubleQuotes
+    "wraps the receiver into double quotes.
+     This is the JavaScript standard quote function."
+
+    ^ '"',self,'"'
+
+    "
+     'hello' withDoubleQuotes     
+    "
+!
+
 withEscapes
     <resource: #obsolete>
     "has been renamed; the name withEscapes is misleading"
@@ -7106,13 +9260,15 @@
                  (i.e. if the receiver contains newLine characters,
                   no tabs are inserted after those lineBreaks)"
 
-    |idx   "{ SmallInteger }"
-     nTabs "{ SmallInteger }"
+    |idx   "{ Class:SmallInteger }"
+     nTabs "{ Class:SmallInteger }"
      newString|
 
     idx := self findFirst:[:c | (c ~~ Character space)].
     nTabs := (idx-1) // 8.
-    nTabs <= 0 ifTrue:[^ self].
+    nTabs <= 0 ifTrue:[
+        ^ self.
+    ].
 
     "any tabs"
     newString := self species new:(self size - (nTabs * 7)).
@@ -7128,6 +9284,8 @@
      '                7890' withTabs
      '                 890' withTabs
     "
+
+    "Modified (format): / 11-06-2020 / 17:44:15 / Stefan Vogel"
 !
 
 withTabsExpanded
@@ -7173,30 +9331,32 @@
      otherwise a new string is returned.
      This does handle multiline strings."
 
-    |col    "{ SmallInteger }"
+    |col    "{ Class:SmallInteger }"
      str ch
-     dstIdx "{ SmallInteger }"
-     newSz  "{ SmallInteger }"
-     sz "{ SmallInteger }"
-     hasEmphasis e|
-
-    (self includes:(Character tab)) ifFalse:[^ self].
+     dstIdx "{ Class:SmallInteger }"
+     newSz  "{ Class:SmallInteger }"
+     sz "{ Class:SmallInteger }"
+     hasEmphasis e species|
+
+    (self includes:Character tab) ifFalse:[
+        ^ self
+    ].
 
     sz := self size.
 
-    "/ count the new size first, instead of
+    "/ compute the new size first, instead of
     "/ multiple resizing (better for large strings)
 
     col := 1. newSz := 0.
     1 to:sz do:[:srcIdx |
         ch := self at:srcIdx.
-        ch == Character tab ifFalse:[
+        ch ~~ Character tab ifTrue:[
             col := col + 1.
             newSz := newSz + 1.
             ch == Character cr ifTrue:[
                 col := 1
             ].
-        ] ifTrue:[
+        ] ifFalse:[
             (col \\ numSpaces) to:numSpaces do:[:ii |
                 newSz := newSz + 1.
                 col := col + 1
@@ -7204,19 +9364,20 @@
         ]
     ].
 
-    self isText ifTrue:[ 
-        str := Text string: (self string class new: newSz).
+    species := self species.
+    (species == Text and:[self bitsPerCharacter > 8]) ifTrue:[
+        str := Text string:(self string species new:newSz)
     ] ifFalse:[
-        str := self species new:newSz.
-    ].
-
+        str := species new:newSz.
+    ].    
+    
     hasEmphasis := self hasChangeOfEmphasis.
 
     col := 1. dstIdx := 1.
     1 to:sz do:[:srcIdx |
         ch := self at:srcIdx.
 
-        ch == Character tab ifFalse:[
+        ch ~~ Character tab ifTrue:[
             col := col + 1.
             ch == Character cr ifTrue:[
                 col := 1
@@ -7227,7 +9388,7 @@
             ].
             str at:dstIdx put:ch.
             dstIdx := dstIdx + 1
-        ] ifTrue:[
+        ] ifFalse:[
             (col \\ numSpaces) to:numSpaces do:[:ii |
                 str at:dstIdx put:Character space.
                 dstIdx := dstIdx + 1.
@@ -7260,10 +9421,16 @@
              with:Character cr
              with:Character tab
              with:$2) withTabsExpanded
+
+     (Unicode16String with:Character tab
+             with:$1
+             with:Character cr
+             with:Character tab
+             with:$2) asText withTabsExpanded
     "
 
     "Modified: / 12-05-1996 / 13:05:10 / cg"
-    "Modified: / 21-04-2015 / 15:40:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 11-06-2020 / 19:30:59 / Stefan Vogel"
 !
 
 withoutAllSpaces
@@ -7289,7 +9456,7 @@
 
 withoutCEscapes
     "return a new string consisting of receiver's characters
-     with all \X-character escapes replaced by corresponding-characters.
+     with all \X-character escapes replaced by corresponding characters.
      (similar to the way C-language Strings are converted).
      The following escapes are supported:
         \r      return character
@@ -7310,7 +9477,7 @@
 
      Although easily implementable, this is NOT done automatically
      by the compiler (due to a lack of a language standard for this).
-     However, the compiler may detect sends ot #withEscapes to string literals
+     However, the compiler may detect sends of #withEscapes to string literals
      and place a modified string constant into the binary/byte-code.
      Therefore, no runtime penalty will be payed for using these escapes.
      (not in pre 2.11 versions)
@@ -7321,75 +9488,78 @@
            but it cannot be changed easily, as these methods are already used heavily
     "
 
-    |val     "{ SmallInteger }"
+    |val     "{ Class:SmallInteger }"
      in out nextChar nDigits|
 
     "
      first, see if there is any escape; if not, return the receiver unchanged
     "
-    (self includes:$\) ifFalse:[^ self ].
-
-    self hasChangeOfEmphasis ifTrue:[ self error:'emphasis not supported' ].
-    out := CharacterWriteStream on:(String new:self size - 1).
-
+    (self includes:$\) ifFalse:[
+        ^ self.
+    ].
+    self hasChangeOfEmphasis ifTrue:[ 
+        self error:'emphasis not supported'.
+    ].
+    out := CharacterWriteStream new:(self size - 1).
     in := ReadStream on:self.
+    
     [in atEnd] whileFalse:[
         nextChar := in next.
-        nextChar == $\ ifTrue:[
-            in atEnd ifTrue:[
+        (nextChar == $\ and:[in atEnd not]) ifTrue:[
+            nextChar := in next.
+            nextChar == $r ifTrue:[
+                nextChar := Character return
+            ] ifFalse:[ nextChar == $n ifTrue:[
+                nextChar := Character nl
+            ] ifFalse:[ nextChar == $b ifTrue:[
+                nextChar := Character backspace
+            ] ifFalse:[ nextChar == $f ifTrue:[
+                nextChar := Character newPage
+            ] ifFalse:[ nextChar == $t ifTrue:[
+                nextChar := Character tab
+            ] ifFalse:[ nextChar == $e ifTrue:[
+                nextChar := Character esc
             ] ifFalse:[
-                nextChar := in next.
-                nextChar == $r ifTrue:[
-                    nextChar := Character return
-                ] ifFalse:[ nextChar == $n ifTrue:[
-                    nextChar := Character nl
-                ] ifFalse:[ nextChar == $b ifTrue:[
-                    nextChar := Character backspace
-                ] ifFalse:[ nextChar == $f ifTrue:[
-                    nextChar := Character newPage
-                ] ifFalse:[ nextChar == $t ifTrue:[
-                    nextChar := Character tab
-                ] ifFalse:[ nextChar == $e ifTrue:[
-                    nextChar := Character esc
-                ] ifFalse:[
-                    nextChar == $0 ifTrue:[
-                        val := 0.
-                        nextChar := in peek.
-                        nDigits := 1.
-                        [nextChar notNil and:[nextChar isDigit and:[nDigits <= 3]]] whileTrue:[
-                            val := (val * 8) + nextChar digitValue.
-                            nextChar := in nextPeek.
-                            nDigits := nDigits + 1.
-                        ].
-                        nextChar := Character value:val.
-                    ] ifFalse:[
-                        val := 0.
-                        nextChar == $x ifTrue:[
-                            2 timesRepeat:[
-                                nextChar := in next.
-                                val := (val * 16) + nextChar digitValue.
-                            ].
-                            nextChar := Character value:val.
-                        ] ifFalse:[
-                            nextChar == $u ifTrue:[
-                                4 timesRepeat:[
-                                    nextChar := in next.
-                                    val := (val * 16) + nextChar digitValue.
-                                ].
-                                nextChar := Character value:val.
-                            ] ifFalse:[
-                                nextChar == $U ifTrue:[
-                                    8 timesRepeat:[
-                                        nextChar := in next.
-                                        val := (val * 16) + nextChar digitValue.
-                                    ].
-                                    nextChar := Character value:val.
-                                ]
-                            ]
-                        ]
-                    ]
-                ]]]]]].
-            ].
+                val := 0.
+                nDigits := 1.
+                nextChar == $0 ifTrue:[
+                    "/ 3 octal digits
+                    nextChar := in peek.
+                    [nextChar notNil and:[nextChar isDigit and:[nDigits <= 3]]] whileTrue:[
+                        val := (val * 8) + nextChar digitValue.
+                        nextChar := in nextPeek.
+                        nDigits := nDigits + 1.
+                    ].
+                    nextChar := Character value:val.
+                ] ifFalse:[nextChar == $x ifTrue:[
+                    "/ 2 hexadecimal digits
+                    nextChar := in peek.
+                    [nextChar notNil and:[nextChar isHexDigit and:[nDigits <= 2]]] whileTrue:[
+                        val := (val * 16) + nextChar digitValue.
+                        nextChar := in nextPeek.
+                        nDigits := nDigits + 1.
+                    ].
+                    nextChar := Character value:val.
+                ] ifFalse:[nextChar == $u ifTrue:[
+                    "/ 4 hex-digit unicode
+                    nextChar := in peek.
+                    [nextChar notNil and:[nextChar isHexDigit and:[nDigits <= 4]]] whileTrue:[
+                        val := (val * 16) + nextChar digitValue.
+                        nextChar := in nextPeek.
+                        nDigits := nDigits + 1.
+                    ].
+                    nextChar := Character value:val.
+                ] ifFalse:[nextChar == $U ifTrue:[
+                    "/ 8 hex-digit unicode        
+                    nextChar := in peek.
+                    [nextChar notNil and:[nextChar isHexDigit and:[nDigits <= 8]]] whileTrue:[
+                        val := (val * 16) + nextChar digitValue.
+                        nextChar := in nextPeek.
+                        nDigits := nDigits + 1.
+                    ].
+                    nextChar := Character value:val.
+                ]]]]
+            ]]]]]].
         ].
         out nextPut:nextChar.
     ].
@@ -7409,15 +9579,21 @@
      '0\x080' withoutCEscapes
      '0\u12340' withoutCEscapes
      '0\U123456780' withoutCEscapes
+     '0\U12abc+' withoutCEscapes
+     '0\U12+' withoutCEscapes
      '0\0a' withoutCEscapes
      '0\00a' withoutCEscapes
      '0\000a' withoutCEscapes
      '0\0000a' withoutCEscapes
      '0\00000a' withoutCEscapes
      '0\03770' withoutCEscapes
+     '0\\0' withoutCEscapes
+     '0\+0' withoutCEscapes
     "
 
     "Created: / 25-01-2012 / 10:41:44 / cg"
+    "Modified (comment): / 23-08-2017 / 11:07:43 / mawalch"
+    "Modified (comment): / 11-06-2020 / 18:36:58 / Stefan Vogel"
 !
 
 withoutCRs
@@ -7513,28 +9689,53 @@
     "Modified: / 30-04-2016 / 10:01:00 / cg"
 !
 
-withoutQuotes
-    "/ remove quotes ($" and $') from the front and end of myself (if matching)"
-
-    |firstChar|
-
-    self isEmpty ifTrue:[^ self].
-
-    firstChar := self first.
-    ((firstChar == $") or:[firstChar == $']) ifFalse:[^ self].
-
-    self last == firstChar ifTrue:[
-        ^ self copyFrom:2 to:(self size-1)
+withoutPrefix:aStringOrCharacter caseSensitive:caseSensitive
+    "if the receiver startsWith aString, return a copy without it.
+     Otherwise return the receiver"
+
+    (self startsWith:aStringOrCharacter caseSensitive:caseSensitive) ifTrue:[
+        aStringOrCharacter isCharacter ifTrue:[
+            ^ self copyFrom:2
+        ] ifFalse:[    
+            ^ self copyFrom:aStringOrCharacter size+1
+        ].
     ].
     ^ self
 
-    "/
-    "/ '"hello"' withoutQuotes
-    "/ '''hello''' withoutQuotes
-    "/ 'hello' withoutQuotes
-    "/ '"hello' withoutQuotes
-    "/ 'hello"' withoutQuotes
-    "/
+    "
+     'Helloworld' withoutPrefix:'hello' caseSensitive:false
+     'Helloworld' withoutPrefix:'foo' caseSensitive:false
+     'Helloworld' withoutPrefix:$h caseSensitive:false
+     'Helloworld' withoutPrefix:#( $h ) caseSensitive:false
+    "
+
+    "Created: / 27-07-2018 / 08:30:03 / Claus Gittinger"
+    "Modified: / 31-07-2018 / 17:05:53 / Claus Gittinger"
+    "Modified (comment): / 24-05-2019 / 09:23:30 / Claus Gittinger"
+!
+
+withoutQuotes
+    "/ removes quotes ($" and $') from the front and end of myself (if present and matching)"
+
+    |firstChar mySize|
+
+    ((mySize := self size) >= 2) ifTrue:[
+        firstChar := self at:1.
+        ((firstChar == $") or:[firstChar == $']) ifTrue:[
+            (self at:mySize) == firstChar ifTrue:[
+                ^ self copyFrom:2 to:(mySize-1)
+            ].
+        ].
+    ].
+    ^ self
+
+"<<END
+     '"hello"' withoutQuotes   
+     '''hello''' withoutQuotes
+     'hello' withoutQuotes
+     '"hello' withoutQuotes
+     'hello"' withoutQuotes
+END
 !
 
 withoutSeparators
@@ -7573,6 +9774,28 @@
     "
 !
 
+withoutSuffix:aStringOrCharacter caseSensitive:caseSensitive
+    "if the receiver endsWith aString, return a copy without it.
+     Otherwise return the receiver"
+
+    (self endsWith:aStringOrCharacter caseSensitive:caseSensitive) ifTrue:[
+        aStringOrCharacter isCharacter ifTrue:[
+            ^ self copyButLast:1
+        ] ifFalse:[
+            ^ self copyButLast:aStringOrCharacter size
+        ].
+    ].
+    ^ self
+
+    "
+     'helloworld' withoutSuffix:'world'
+     'helloworld' withoutSuffix:'foo'
+    "
+
+    "Created: / 27-07-2018 / 08:30:10 / Claus Gittinger"
+    "Modified: / 31-07-2018 / 17:06:58 / Claus Gittinger"
+!
+
 withoutTrailingSeparators
     "return a copy of myself without trailing separators.
      Notice: this does remove tabs, newline or any other whitespace.
@@ -7581,14 +9804,16 @@
     ^ self withoutTrailingForWhich:[:ch | ch isSeparator]
 
     "
-     '    foo    ' withoutTrailingSeparators
-     'foo    '     withoutTrailingSeparators
-     '    foo'     withoutTrailingSeparators
-     '       '     withoutTrailingSeparators
-     'foo'         withoutTrailingSeparators
-     ('  ' , Character tab asString , ' foo   ') withoutTrailingSeparators inspect
-     ('   foo' , Character tab asString) withoutTrailingSeparators inspect
-    "
+     '    foo    ' asUnicodeString withoutTrailingSeparators
+     'foo    '     asUnicodeString withoutTrailingSeparators
+     '    foo'     asUnicodeString withoutTrailingSeparators
+     '       '     asUnicodeString withoutTrailingSeparators
+     'foo'         asUnicodeString withoutTrailingSeparators
+     ('  ' , Character tab, ' foo   ') asUnicodeString withoutTrailingSeparators inspect
+     ('   foo' , Character tab) asUnicodeString withoutTrailingSeparators inspect
+    "
+
+    "Modified (comment): / 12-12-2019 / 14:15:09 / Stefan Vogel"
 ! !
 
 !CharacterArray methodsFor:'substring searching'!
@@ -7662,18 +9887,10 @@
     "
 !
 
-findString:subString startingAt: startIndex caseSensitive:caseSensitive
-    "find a substring. if found, return the index;
-     if not found, return 0."
-
-    ^ self indexOfSubCollection:subString startingAt:startIndex ifAbsent:0 caseSensitive:caseSensitive
-
-    "
-     'hello world' findString:'LLo' caseSensitive:true
-     'hello world' findString:'LLo' caseSensitive:false
-    "
-
-    "Created: / 01-06-2020 / 21:10:01 / Jan Vrany <jan.vrany@labware.com>"
+findString:key startingAt:start caseSensitive:caseSensitive
+    ^ self indexOfSubCollection:key startingAt:start ifAbsent:[0] caseSensitive:caseSensitive
+
+    "Created: / 13-07-2017 / 12:44:50 / cg"
 !
 
 findString:subString startingAt:index ifAbsent:exceptionBlock
@@ -7720,30 +9937,96 @@
     "
 !
 
-indexOfString: aString
+indexOfString:aString
+    "VSE and V'age compatibility"
+    "find a substring. If found, return the index; if not found, return 0."
+
+    ^ self indexOfSubCollection:aString startingAt:1 ifAbsent:[0] caseSensitive:true 
+
+    "
+     'hello world' indexOfString:'hello' -> 1
+     'hello world' indexOfString:'world' -> 7
+     'hello world' indexOfString:'World' -> 0
+     'hello world' indexOfString:'World' caseSensitive:false -> 7
+    "
+
+    "Modified (format): / 08-06-2018 / 14:43:15 / Claus Gittinger"
+!
+
+indexOfString:aString caseSensitive:caseSensitive
     "VSE and V'age compatibility"
     "find a substring. If found, return the index; if not found, return 0."
 
-    ^ self indexOfSubCollection: aString startingAt:1 ifAbsent:[0]
+    ^ self indexOfSubCollection:aString startingAt:1 ifAbsent:[0] caseSensitive:caseSensitive 
+
+    "
+     'hello world' indexOfString:'hello' -> 1
+     'hello world' indexOfString:'world' -> 7
+     'hello world' indexOfString:'World' -> 0
+     'hello world' indexOfString:'World' caseSensitive:false -> 7
+    "
+
+    "Created: / 08-06-2018 / 14:39:18 / Claus Gittinger"
+!
+
+indexOfString:aString caseSensitive:caseSensitive ifAbsent:exceptionValue
+    "VSE and V'age compatibility"
+    "find a substring. If found, return the index; if not found, return 0."
+
+    ^ self indexOfSubCollection:aString startingAt:1 ifAbsent:exceptionValue caseSensitive:caseSensitive  
+
+    "
+     'abcdefabcdef' indexOfString:'fab' ifAbsent:[999] -> 6
+     'abcdefabcdef' indexOfString:'Fab' ifAbsent:[999] -> 999
+     'abcdefabcdef' indexOfString:'Fab' caseSensitive:false ifAbsent:[999] -> 6
+     'abcdefabcdef' indexOfString:'xxx' caseSensitive:false ifAbsent:[999] -> 999
+    "
+
+    "Created: / 08-06-2018 / 14:40:21 / Claus Gittinger"
+!
+
+indexOfString:aString caseSensitive:caseSensitive 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] caseSensitive:caseSensitive
+
+    "Created: / 08-06-2018 / 14:44:17 / Claus Gittinger"
+!
+
+indexOfString:aString caseSensitive:caseSensitive startingAt:startIndex ifAbsent:exceptionalValue
+    "VSE and V'age compatibility"
+    "find a substring.
+     If found, return the index; if not found, the value from exceptionalValue."
+
+    ^ self indexOfSubCollection:aString startingAt:startIndex ifAbsent:exceptionalValue caseSensitive:caseSensitive
+
+    "Created: / 08-06-2018 / 14:42:33 / Claus Gittinger"
 !
 
 indexOfString:aString ifAbsent:exceptionValue
     "VSE and V'age compatibility"
     "find a substring. If found, return the index; if not found, return 0."
 
-    ^ self indexOfSubCollection: aString startingAt:1 ifAbsent:exceptionValue
-
-    "
-     'abcdefabcdef' indexOfString:'fab' ifAbsent:[999]
-     'abcdefabcdef' indexOfString:'xxx' ifAbsent:[999]
-    "
+    ^ self indexOfSubCollection:aString startingAt:1 ifAbsent:exceptionValue caseSensitive:true 
+
+    "
+     'abcdefabcdef' indexOfString:'fab' ifAbsent:[999] -> 6
+     'abcdefabcdef' indexOfString:'Fab' ifAbsent:[999] -> 999
+     'abcdefabcdef' indexOfString:'Fab' caseSensitieve:false ifAbsent:[999] -> 999
+     'abcdefabcdef' indexOfString:'xxx' ifAbsent:[999] -> 999
+    "
+
+    "Modified: / 08-06-2018 / 14:43:44 / Claus Gittinger"
 !
 
 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]
+    ^ self indexOfSubCollection:aString startingAt:startIndex ifAbsent:[0] caseSensitive:true
+
+    "Modified: / 08-06-2018 / 14:37:52 / Claus Gittinger"
 !
 
 indexOfString:aString startingAt:startIndex ifAbsent:exceptionalValue
@@ -7751,23 +10034,27 @@
     "find a substring.
      If found, return the index; if not found, the value from exceptionalValue."
 
-    ^ self indexOfSubCollection:aString startingAt:startIndex ifAbsent:exceptionalValue
+    ^ self indexOfSubCollection:aString startingAt:startIndex ifAbsent:exceptionalValue caseSensitive:true
+
+    "Modified: / 08-06-2018 / 14:38:12 / Claus Gittinger"
 !
 
 indexOfSubCollection:subString caseSensitive:caseSensitive
     "find a substring, starting at index. if found, return the index;
-     if not found, return the result of evaluating exceptionBlock.
-     This is a q&d hack - not very efficient"
+     if not found, return the result of evaluating exceptionBlock."
 
     ^ self indexOfSubCollection:subString startingAt:1 ifAbsent:[0] caseSensitive:caseSensitive.
+
+    "Modified (comment): / 28-03-2017 / 15:53:30 / stefan"
 !
 
 indexOfSubCollection:subString startingAt:index ifAbsent:exceptionBlock
     "find a substring, starting at index. if found, return the index;
-     if not found, return the result of evaluating exceptionBlock.
-     This is a q&d hack - not very efficient"
+     if not found, return the result of evaluating exceptionBlock."
 
     ^ self indexOfSubCollection:subString startingAt:index ifAbsent:exceptionBlock caseSensitive:true.
+
+    "Modified (comment): / 28-03-2017 / 15:53:14 / stefan"
 !
 
 indexOfSubCollection:subString startingAt:index ifAbsent:exceptionBlock caseSensitive:caseSensitive
@@ -7779,13 +10066,12 @@
      startIndex "{ Class: SmallInteger }"
      subSize    "{ Class: SmallInteger }"
      mySize     "{ Class: SmallInteger }"
-     runIdx     "{ Class: SmallInteger }"
-     tester|
+     runIdx     "{ Class: SmallInteger }"|
 
     subSize := subString size.
     subSize == 0 ifTrue:[
         subString isString ifFalse:[
-           self error:'non string argument' mayProceed:true.
+           self proceedableError:'non string argument'.
         ].
         "empty string does not match"
         ^ 0.
@@ -7796,22 +10082,22 @@
     mySize := self size.
     firstChar := subString at:1.
     caseSensitive ifTrue:[
-        tester := [:c1 :c2 | c1 = c2 ].
         startIndex := self indexOf:firstChar startingAt:index.
     ] ifFalse:[
-        tester := [:c1 :c2 | c1 sameAs: c2 ].
         startIndex := self findFirst:[:c | c sameAs:firstChar] startingAt:index.
     ].
-    [startIndex == 0] whileFalse:[
+    [startIndex ~~ 0] whileTrue:[
         runIdx := startIndex.
         found := true.
         1 to:subSize do:[:i |
             runIdx > mySize ifTrue:[
                 found := false
             ] ifFalse:[
-                (tester value:(subString at:i) value:(self at:runIdx)) ifFalse:[
-                    found := false
-                ]
+                caseSensitive ifTrue:[
+                    (subString at:i) ~= (self at:runIdx) ifTrue:[found := false].
+                ] ifFalse:[
+                    ((subString at:i) sameAs:(self at:runIdx)) ifFalse:[found := false].
+                ].
             ].
             runIdx := runIdx + 1
         ].
@@ -7826,7 +10112,14 @@
     ].
     ^ exceptionBlock value
 
-    "Modified: 23.2.1996 / 15:35:15 / cg"
+    "
+        'АБВГДЕЖ' asLowercase indexOfSubCollection:'ВГДЕ' startingAt:1 ifAbsent:nil caseSensitive:false.
+        'АБВГДЕЖ' indexOfSubCollection:'ВГДЕ' startingAt:1 ifAbsent:nil caseSensitive:true.
+    "
+
+    "Modified: / 23-02-1996 / 15:35:15 / cg"
+    "Modified (comment): / 28-03-2017 / 16:05:48 / stefan"
+    "Modified: / 24-05-2018 / 14:55:38 / Claus Gittinger"
 !
 
 indexOfSubCollection:subString startingAt:index ifAbsent:exceptionBlock caseSensitive:caseSensitive ignoreDiacritics:ignoreDiacritics
@@ -7845,7 +10138,7 @@
     subSize := subString size.
     subSize == 0 ifTrue:[
         subString isString ifFalse:[
-           self error:'non string argument' mayProceed:true.
+           self proceedableError:'non string argument'.
         ].
         "empty string does not match"
         ^ 0.
@@ -7901,6 +10194,8 @@
      'bla depot bla dépots' indexOfSubCollection:'dep' startingAt:1 ifAbsent:0 caseSensitive:false ignoreDiacritics:false. 5
      'bla depot bla dépots' indexOfSubCollection:'dep' startingAt:6 ifAbsent:0 caseSensitive:false ignoreDiacritics:false. 0
     "
+
+    "Modified: / 24-05-2018 / 14:55:43 / Claus Gittinger"
 !
 
 lastIndexOfString:aString
@@ -7957,6 +10252,61 @@
     "
 !
 
+occurrencesOfString:aSubString
+    "count how often the argument aSubString is contained in the receiver"
+
+    ^ self occurrencesOfString:aSubString caseSensitive:true
+
+    "
+     'aa' indexOfString:'aa' startingAt:1
+
+     '' occurrencesOfString:'aa'
+     'a' occurrencesOfString:'aa'  
+     'aa' occurrencesOfString:'aa'  
+     ' aa ' occurrencesOfString:'aa'  
+     ' aa a' occurrencesOfString:'aa'  
+     ' aaaa' occurrencesOfString:'aa'  
+     ' aa aa ' occurrencesOfString:'aa'  
+     ' aa bb ab ba aa ab' occurrencesOfString:'aa'  
+     ' aa bb cc aa bb cc aa bb ' occurrencesOfString:'aa'  
+    "
+
+    "Created: / 25-05-2019 / 08:57:14 / Claus Gittinger"
+!
+
+occurrencesOfString:aSubString caseSensitive:caseSensitive
+    "count how often the argument aSubString is contained in the receiver"
+
+    |idx count|
+
+    idx := 1.
+    count := 0.
+    [idx ~~ 0] whileTrue:[
+        idx := self indexOfString:aSubString caseSensitive:caseSensitive startingAt:idx.
+        idx ~~ 0 ifTrue:[
+            count := count + 1.
+            idx := idx + aSubString size
+        ]
+    ].
+    ^ count
+
+    "
+     'aa' indexOfString:'aa' startingAt:1
+
+     '' occurrencesOfString:'aA' caseSensitive:false
+     'a' occurrencesOfString:'aA' caseSensitive:false 
+     'aa' occurrencesOfString:'aA' caseSensitive:false  
+     ' aa ' occurrencesOfString:'aA' caseSensitive:false  
+     ' aa a' occurrencesOfString:'aA' caseSensitive:false  
+     ' aaaa' occurrencesOfString:'aA' caseSensitive:false  
+     ' aa aa ' occurrencesOfString:'aA' caseSensitive:false  
+     ' aa bb ab ba aa ab' occurrencesOfString:'aA' caseSensitive:false  
+     ' aa bb cc aa bb cc aa bb ' occurrencesOfString:'aA' caseSensitive:false  
+    "
+
+    "Created: / 25-05-2019 / 09:06:46 / Claus Gittinger"
+!
+
 rangeOfSubCollection:subString startingAt:start ifAbsent:exceptionValue caseSensitive:caseSensitive
     "find a substring. if found, return the start- and endIndex;
      if not found, return the value of exceptionValue."
@@ -8003,81 +10353,18 @@
      '_:' argumentCount
      '_:_:' argumentCount
      '<->' argumentCount
-    "
-!
-
-characterSize
-    "answer the size in bits of my largest character (actually only 7, 8, 16 or 32)"
-
-    |string max
-     sz "{ Class:SmallInteger}" |
-
-    (string := self string) ~~ self ifTrue:[
-        ^ 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.
-            ].
-        ].
-    ].
-
-    ^ max.
-
-    "
-     'hello' characterSize
-     'hello' asUnicode32String characterSize
-     'helloü' asUnicode32String characterSize
-     'hello' asText allBold characterSize
-    "
-!
-
-contains8BitCharacters
-    <resource: #obsolete>
-
-    ^ self containsNon7BitAscii
-!
-
-containsNon7BitAscii
-    "return true, if the underlying string contains 8BitCharacters (or widers)
-     (i.e. if it is non-ascii)"
-
-    |string
-     sz "{ Class:SmallInteger }"|
-
-    (string := self string) ~~ self ifTrue:[
-        ^ string containsNon7BitAscii
-    ].
-    sz := self size.
-    1 to:sz do:[:idx|
-        (self at:idx) codePoint > 16r7F ifTrue:[
-            ^ true.
-        ].
-    ].
-    ^ false.
-
-    "
-     'hello' asUnicode32String containsNon7BitAscii
-     'hello üöä' asUnicode32String containsNon7BitAscii
-     'hello' asUnicode32String asText allBold containsNon7BitAscii
-     'hello üö' asUnicode32String asText allBold containsNon7BitAscii
-    "
+     '<' argumentCount
+     #'<' argumentCount
+    "
+
+    "Modified (comment): / 06-02-2017 / 13:48:57 / cg"
 !
 
 isAlphaNumeric
     "return true, if the receiver is some alphanumeric word;
      i.e. consists of a letter followed by letters or digits."
 
-    self size == 0 ifTrue:[
+    self isEmpty ifTrue:[
         "mhmh what is this ?"
         ^ false
     ].
@@ -8102,7 +10389,7 @@
 !
 
 isBinarySelector
-    "treating the receiver as a message selector, return true if its a binary selector.
+    "treating the receiver as a message selector, return true if it's a binary selector.
      Notice, that st/x does not have a size <= 2 limit for unaries"
 
     |binopChars|
@@ -8126,56 +10413,24 @@
      '::' isBinarySelector
     "
 
-    "Modified: 4.1.1997 / 14:16:14 / cg"
+    "Modified: / 04-01-1997 / 14:16:14 / cg"
+    "Modified (comment): / 13-02-2017 / 19:57:29 / cg"
 !
 
 isBlank
     "return true, if the receiver contains spaces only"
 
-    ^ (self contains:[:char | char ~~ Character space]) not
+    ^ self size == 0 or:[(self contains:[:char | char ~~ Character space]) not]
 
     "
      '' isBlank
+     '' asUnicode16String isBlank
      '   a    ' isBlank
      '        ' isBlank
      '        ' asUnicode16String isBlank
     "
-!
-
-isInfix
-    "return true, if the receiver is a binary message selector"
-
-    ^ self first isLetterOrDigit not
-
-    "
-     #at:put: isInfix
-     #at: isInfix
-     #+ isInfix
-     #size isInfix
-    "
-
-    "Created: / 1.11.1997 / 12:34:55 / cg"
-    "Modified: / 1.11.1997 / 12:36:37 / cg"
-!
-
-isKeyword
-    "return true, if the receiver is a keyword message selector.
-     This is a quick check, which only looks at the last character.
-     Should only be used, if we already know that the receiver forms a valid selector.
-     To check an arbitrary string, use isKeywordSelector.
-     Bad naming, but compatibility is asking for it."
-
-    ^ self last == $:
-
-    "
-     #at:put: isKeyword
-     #at: isKeyword
-     #+ isKeyword
-     #size isKeyword
-    "
-
-    "Created: / 01-11-1997 / 12:34:55 / cg"
-    "Modified (comment): / 30-04-2016 / 18:19:11 / cg"
+
+    "Modified (comment): / 14-09-2018 / 10:04:18 / Stefan Vogel"
 !
 
 isKeywordSelector
@@ -8199,7 +10454,7 @@
             char == $: ifTrue:[
                 state := #gotColon.
             ] ifFalse:[
-                (char isLetterOrDigit or:[char == $_]) ifFalse:[^ false].
+                (char isLetterOrDigitOrUnderline) ifFalse:[^ false].
             ].
         ].
     ].
@@ -8222,6 +10477,7 @@
     "
 
     "Modified (comment): / 30-04-2016 / 18:20:14 / cg"
+    "Modified: / 05-06-2019 / 17:05:53 / Claus Gittinger"
 !
 
 isNameSpaceSelector
@@ -8232,17 +10488,8 @@
      is legal, and this can be checked quickly by just looking at the first character.
      You cannot easily change this algorithm here, as it is also known by the VM's lookup function."
 
-    |i|
-
     (self at:1) == $: ifFalse:[^ false].
-
-    i := self indexOf:$: startingAt:2.
-    i == 0 ifTrue:[^ false].
-    self size <= (i+1) ifTrue:[^ false].
-    (self at:i+1) == $: ifFalse:[^ false].
-    (self at:i+2) == $: ifTrue:[^ false].
-    "/ could check if the rest after the ns-prefix and colons is a valid selector...
-    ^ true
+    ^ (self indexOfSubCollection:'::' startingAt:3 ifAbsent:0 caseSensitive:true) ~~ 0.
 
     "test:
      self assert:('+' isNameSpaceSelector) not.
@@ -8254,26 +10501,7 @@
     "
 
     "Created: / 05-03-2007 / 11:35:31 / cg"
-!
-
-isNumeric
-    "return true, if the receiver is some numeric word;
-     i.e. consists only of digits."
-
-    self size == 0 ifTrue:[
-        ^ false
-    ].
-    ^ self conform:[:char | char isDigit]
-
-    "
-     'helloWorld' isNumeric
-     'foo1234' isNumeric
-     'f1234' isNumeric
-     '1234' isNumeric
-     '+' isNumeric
-    "
-
-    "Modified: / 13-10-2006 / 12:54:12 / cg"
+    "Modified: / 08-05-2019 / 14:41:30 / Stefan Vogel"
 !
 
 isPlainString
@@ -8302,9 +10530,21 @@
     "Answer true if the receiver contains only chars in an ANSI unary method selector, false otherwise."
 
     ^ (self first isLetterOrUnderline)
-      and:[ self conform: [ :chr | chr isLetterOrDigit or:[chr == $_] ]]
+      and:[ self conform: [ :chr | chr isLetterOrDigitOrUnderline ]]
+
+    "
+     'foobar' isUnarySelector
+     '_foobar' isUnarySelector
+     '_' isUnarySelector
+     'abc.def' isUnarySelector
+     'abc123' isUnarySelector
+     '123abc123' isUnarySelector
+     '123abc' isUnarySelector
+     '123' isUnarySelector
+    "
 
     "Modified: / 13-09-2006 / 11:35:15 / cg"
+    "Modified: / 05-06-2019 / 17:05:59 / Claus Gittinger"
 !
 
 isUnicode16String
@@ -8321,9 +10561,11 @@
     "true if this is a 2- or 4-byte unicode string
      (i.e. not a single byte string).
      Notice, that the name is misleading:
-     all strings are use unicode encoding"
+     all strings use unicode encoding"
 
     ^ false
+
+    "Modified (comment): / 21-11-2019 / 18:25:19 / Stefan Vogel"
 !
 
 isValidSmalltalkIdentifier
@@ -8333,7 +10575,7 @@
 
     scanner := Compiler new.
     scanner source:(self readStream).
-    Parser parseErrorSignal handle:[:ex |
+    ParseError handle:[:ex |
         tok := nil.
     ] do:[
         tok := scanner nextToken.
@@ -8363,47 +10605,6 @@
         ^ string isWideString.
     ].
     ^ self contains:[:aCharacter | aCharacter codePoint > 16rFF].
-!
-
-numArgs
-    <resource: #obsolete>
-    "treating the receiver as a message selector, return how many arguments would it take.
-     Please use argumentCount for ANSI compatibility."
-
-    ^ self argumentCount
-!
-
-partsIfSelector
-    "treat the receiver as a message selector, return a collection of parts.
-     Notice: this is more tolerant than Smalltalk's syntax would suggest;
-     especially it allows for empty keyword parts between colons.
-     This is not (and should not be checked here), to allow parsing of
-     degenerate selectors as appearing with objectiveC."
-
-    |idx1 "{ Class: SmallInteger }"
-     coll idx2 sz|
-
-    coll := OrderedCollection new.
-    idx1 := 1.
-    sz := self size.
-    [
-        idx2 := self indexOf:$: startingAt:idx1.
-        (idx2 == 0 or:[idx2 == sz]) ifTrue:[
-            coll add:(self copyFrom:idx1).
-            ^ coll
-        ].
-        coll add:(self copyFrom:idx1 to:idx2).
-        idx1 := idx2 + 1
-    ] loop.
-
-    "
-     'foo:' partsIfSelector
-     'foo:bar:' partsIfSelector
-     'foo::::' partsIfSelector
-     #foo:bar: partsIfSelector
-     'hello' partsIfSelector
-     '+' partsIfSelector
-    "
 ! !
 
 !CharacterArray methodsFor:'tracing'!
@@ -8424,7 +10625,6 @@
     ^ aVisitor visitString:self with:aParameter
 ! !
 
-
 !CharacterArray class methodsFor:'documentation'!
 
 version
@@ -8433,11 +10633,6 @@
 
 version_CVS
     ^ '$Header$'
-!
-
-version_HG
-
-    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/SequenceableCollection.st	Mon Aug 31 11:59:30 2020 +0100
+++ b/SequenceableCollection.st	Mon Aug 31 12:01:25 2020 +0100
@@ -62,21 +62,6 @@
 "
 ! !
 
-!SequenceableCollection class methodsFor:'initialization'!
-
-initialize
-"/ now a class based exception
-"/ method here left as a comment for a while.
-"/ will go away soon...
-"/    MissingClassInLiteralArrayErrorSignal isNil ifTrue:[
-"/        MissingClassInLiteralArrayErrorSignal := Error newSignalMayProceed:true.
-"/        MissingClassInLiteralArrayErrorSignal nameClass:self message:#missingClassInLiteralArrayErrorSignal.
-"/        MissingClassInLiteralArrayErrorSignal notifierString:'Missing class in literal encoding'.
-"/    ]
-
-    "Created: / 18.5.1999 / 14:49:51 / cg"
-! !
-
 !SequenceableCollection class methodsFor:'instance creation'!
 
 decodeFromLiteralArray:anArray
@@ -117,39 +102,37 @@
 
     |totalSize newColl idx|
 
-    totalSize := aCollectionOfCollections
-			inject:0
-			into:[:sumSoFar :el | sumSoFar + el size].
+    totalSize := aCollectionOfCollections sum:[:el| el size].
     newColl := self new:totalSize.
     idx := 1.
     aCollectionOfCollections do:[:el |
-	|sz|
-
-	sz := el size.
-	newColl replaceFrom:idx to:(idx+sz-1) with:el startingAt:1.
-	idx := idx + sz
+        |sz|
+
+        sz := el size.
+        newColl replaceFrom:idx to:(idx+sz-1) with:el startingAt:1.
+        idx := idx + sz
     ].
     ^ newColl
 
     "
      this method optimizes the following (common) operation:
 
-	 |s|
-
-	 s := ''.
-	 #('hello' ' ' 'world' ' ' 'this is ' 'ST/X') do:[:e|
-	    s := s , e.
-	 ].
-	 s
+         |s|
+
+         s := ''.
+         #('hello' ' ' 'world' ' ' 'this is ' 'ST/X') do:[:e|
+            s := s , e.
+         ].
+         s
 
      String
-	newWithConcatenationOfAll:#('hello' ' ' 'world' ' ' 'this is ' 'ST/X')
+        newWithConcatenationOfAll:#('hello' ' ' 'world' ' ' 'this is ' 'ST/X')
 
      String
-	newWithConcatenationOfAll:#()
+        newWithConcatenationOfAll:#()
 
      Array
-	newWithConcatenationOfAll:#( (1 2 3 4) (5 6 7 8) (9 10 11 12) )
+        newWithConcatenationOfAll:#( (1 2 3 4) (5 6 7 8) (9 10 11 12) )
 
      timing:
      -------
@@ -163,46 +146,50 @@
      arr3 := Array new:10000 withAll:'hello'.
 
      (Array with:arr1 with:arr2 with:arr3) with:#(10000 100 10) do:[:arr :cnt |
-	 t := Time millisecondsToRun:[
-	    cnt timesRepeat:[
-		String
-		    newWithConcatenationOfAll:arr
-	    ]
-	 ].
-	 Transcript showCR:(arr size printString , ' elements - time for #newWithConcatenationOfAll :' , (t/cnt) asFloat printString , 'mS').
-	 Transcript endEntry.
-
-	 t := Time millisecondsToRun:[
-	    cnt timesRepeat:[
-		 |s|
-
-		 s := ''.
-		 arr do:[:e|
-		    s := s , e.
-		 ].
-		 s
-	    ]
-	 ].
-	 Transcript showCR:(arr size printString , ' elements - time for loop over #, :' , (t/cnt) asFloat printString , 'mS').
-	 Transcript endEntry.
+         t := Time millisecondsToRun:[
+            cnt timesRepeat:[
+                String
+                    newWithConcatenationOfAll:arr
+            ]
+         ].
+         Transcript showCR:(arr size printString , ' elements - time for #newWithConcatenationOfAll :' , (t/cnt) asFloat printString , 'mS').
+         Transcript endEntry.
+
+         t := Time millisecondsToRun:[
+            cnt timesRepeat:[
+                 |s|
+
+                 s := ''.
+                 arr do:[:e|
+                    s := s , e.
+                 ].
+                 s
+            ]
+         ].
+         Transcript showCR:(arr size printString , ' elements - time for loop over #, :' , (t/cnt) asFloat printString , 'mS').
+         Transcript endEntry.
      ]
     "
+
+    "Modified: / 22-02-2019 / 09:58:25 / Stefan Vogel"
 !
 
 newWithSize:size
     "return a new collection of size.
      For variable size collections, this is different from #new:,
      in that #new: creates an empty collection with preallocated size,
-     while #withSize: creates a non empty one."
+     while #newWithSize: creates a non empty one."
 
     ^ (self new:size) grow:size.
 
     "
      (OrderedCollection new:10) inspect.
-     (OrderedCollection withSize:10) inspect.
+     (OrderedCollection newWithSize:10) inspect.
      (Array new:10) inspect.
-     (Array withSize:10) inspect.
-    "
+     (Array newWithSize:10) inspect.
+    "
+
+    "Modified (comment): / 09-10-2017 / 17:03:18 / stefan"
 ! !
 
 !SequenceableCollection class methodsFor:'Signal constants'!
@@ -220,7 +207,7 @@
     "Created: / 18.5.1999 / 14:50:04 / cg"
 ! !
 
-!SequenceableCollection class methodsFor:'instance creation-multiDimensional'!
+!SequenceableCollection class methodsFor:'instance creation - multiDimensional'!
 
 _at:nIndices
     "this is a synthetic selector, generated by the compiler,
@@ -232,43 +219,9 @@
     "
 
     ^ self new:nIndices
-!
-
-_at:dim1 at:dim2
-    "this is a synthetic selector, generated by the compiler,
-     if a construct of the form expr[idx...] is parsed.
-     I.e.
-        Array[n,m]
-     generates
-        Array _at:n at:m
-    "
-
-    |data|
-
-    data := self newWithSize:(dim1 * dim2).
-    ^ MultiDimensionalArrayAccessor
-        collection:data
-        dimensions:(Array with:dim1 with:dim2)
-!
-
-_at:dim1 at:dim2 at:dim3
-    "this is a synthetic selector, generated by the compiler,
-     if a construct of the form expr[idx...] is parsed.
-     I.e.
-        Array[n,m,o]
-     generates
-        Array _at:n at:m at:o
-    "
-
-    |data|
-
-    data := self newWithSize:(dim1 * dim2 * dim3).
-    ^ MultiDimensionalArrayAccessor
-        collection:data
-        dimensions:(Array with:dim1 with:dim2 with:dim3)
 ! !
 
-!SequenceableCollection class methodsFor:'instance creation-streaming'!
+!SequenceableCollection class methodsFor:'instance creation - streaming'!
 
 new:newSize streamContents:blockWithArg 
     "create a write-stream on an instance of the receiver-class with initial size,
@@ -302,26 +255,6 @@
     "
 !
 
-streamContents:blockWithArg
-    "create a write-stream on an instance of the receiver-class,
-     evaluate blockWithArg, passing that stream,
-     extract and return the streams contents."
-
-    |stream|
-
-    stream := self writeStream.
-    blockWithArg value:stream.
-    ^ stream contents
-
-    "
-     |rslt|
-
-     rslt := String streamContents:[:s | s nextPutAll:'hello'; space; nextPutAll:'world']
-    "
-
-    "Modified: / 29-03-2007 / 15:20:20 / cg"
-!
-
 streamContents:blockWithArg limitedTo:limit
     "create a limited write-stream on an instance of the receiver-class,
      evaluate blockWithArg, passing that stream,
@@ -397,17 +330,17 @@
     "
 !
 
-writeStream
+writeStream:count
     "create a write-stream on an instance of the receiver-class"
 
-    ^ self writeStreamClass on:(self new:50).
+    ^ self writeStreamClass on:(self new:count).
 
     "
      OrderedCollection writeStream
      Text writeStream
     "
 
-    "Modified: / 09-01-2011 / 10:37:35 / cg"
+    "Created: / 10-01-2018 / 18:32:59 / stefan"
 !
 
 writeStreamWithInitialSize:l
@@ -422,6 +355,83 @@
     "Created: / 09-01-2011 / 10:36:28 / cg"
 ! !
 
+!SequenceableCollection class methodsFor:'instance creation-multiDimensional'!
+
+_at:dim1 at:dim2 
+    "this is a synthetic selector, generated by the compiler,
+     if a construct of the form expr[idx] is parsed.
+     I.e.
+        Array[n][m]
+     generates
+        Array _at:n at:m"
+    
+    |data|
+
+    data := self newWithSize:(dim1 * dim2).
+    ^ MatrixAccessor collection:data dimensions:(Array with:dim1 with:dim2)
+
+    "
+     <pragma: +ArrayIndexSyntaxExtension>
+
+     Array[3][3] inspect.
+     DoubleArray[3][3] inspect.
+     Matrix[3][3] inspect.
+    "
+!
+
+_at:dim1 at:dim2 at:dim3 
+    "this is a synthetic selector, generated by the compiler,
+     if a construct of the form expr[idx...] is parsed.
+     I.e.
+        Array[n][m][o]
+     generates
+        Array _at:n at:m at:o"
+    
+    |data|
+
+    data := self newWithSize:(dim1 * dim2 * dim3).
+    ^ MatrixAccessor collection:data
+        dimensions:(Array with:dim1 with:dim2 with:dim3)
+! !
+
+!SequenceableCollection class methodsFor:'instance creation-streaming'!
+
+streamContents:blockWithArg
+    "create a write-stream on an instance of the receiver-class,
+     evaluate blockWithArg, passing that stream,
+     extract and return the streams contents."
+
+    |stream|
+
+    stream := self writeStream.
+    blockWithArg value:stream.
+    ^ stream contents
+
+    "
+     |rslt|
+
+     rslt := String streamContents:[:s | s nextPutAll:'hello'; space; nextPutAll:'world'].
+     rslt := Text streamContents:[:s | s nextPutAll:'hello' allBold; space; nextPutAll:'world'].
+    "
+
+    "Modified: / 29-03-2007 / 15:20:20 / cg"
+    "Modified (comment): / 28-05-2019 / 15:03:02 / Claus Gittinger"
+!
+
+writeStream
+    "create a write-stream on an instance of the receiver-class"
+
+    ^ self writeStreamClass on:(self new).
+
+    "
+     OrderedCollection writeStream
+     Text writeStream
+    "
+
+    "Modified: / 09-01-2011 / 10:37:35 / cg"
+    "Modified: / 10-01-2018 / 18:33:18 / stefan"
+! !
+
 !SequenceableCollection class methodsFor:'queries'!
 
 isAbstract
@@ -536,7 +546,8 @@
     ^ self atRandom:Random
 
     "
-     #(1 2 3) atRandom
+     #(1 2 3) atRandom 
+     #('a' 'b' 'c') atRandom 
     "
 !
 
@@ -605,53 +616,6 @@
     "
 !
 
-copyWithoutAll:elementsToSkip
-    "return a new collection consisting of a copy of the receiver, with
-     ALL elements equal to any in elementsToSkip are left out.
-     No error is reported, if any in elementsToSkip is not in the collection."
-
-    |n         "{ Class: SmallInteger }"
-     sz        "{ Class: SmallInteger }"
-     srcIndex  "{ Class: SmallInteger }"
-     dstIndex  "{ Class: SmallInteger }"
-     skipIndex "{ Class: SmallInteger }"
-     copy l|
-
-    "the code below may look like overkill,
-     however, for big collections its better to move data
-     around in big chunks"
-
-    n := self occurrencesOfAny:elementsToSkip.
-    n == 0 ifTrue:[^ self copyFrom:1].
-
-    sz := self size.
-    copy := self copyEmptyAndGrow:(sz - n).
-
-    srcIndex := 1.
-    dstIndex := 1.
-
-    n timesRepeat:[
-        skipIndex := self indexOfAny:elementsToSkip startingAt:srcIndex.
-        l := skipIndex - srcIndex.
-        l ~~ 0 ifTrue:[
-            copy replaceFrom:dstIndex to:(dstIndex + l - 1)
-                        with:self startingAt:srcIndex.
-            dstIndex := dstIndex + l
-        ].
-        srcIndex := skipIndex + 1
-    ].
-    l := sz - srcIndex.
-    copy replaceFrom:dstIndex to:(dstIndex + l)
-                with:self startingAt:srcIndex.
-    ^ copy
-
-    "
-     #($a $b $c $d $e $f $g) copyWithoutAll:#($d $b $f)
-     'abcdefghi' copyWithoutAll:'hai'
-     #(90 80 70 80 60 45 80 50) copyWithoutAll:#(80 70 45)
-    "
-!
-
 copyWithoutFirst
     "An alias for copyButFirst: for squeak compatibility.
      Raises an error, if the receiver is empty."
@@ -666,6 +630,32 @@
     "
 !
 
+destroy
+    "used with cryptographic keys, to wipe their contents after use"
+
+    self clearContents
+!
+
+forceTo:newSize paddingWith:padding
+    "sigh: a bad name; should be named forceToSize:..."
+
+    self size > newSize ifTrue:[
+        ^ self copyTo:newSize
+    ].
+    self size < newSize ifTrue:[
+        ^ (self species new:newSize) 
+            atAllPut:padding;
+            replaceFrom:1 with:self startingAt:1;
+            yourself.
+    ].
+    ^ self.
+
+    "
+     #[1 2 3 4] forceTo:10 paddingWith:255
+     #[1 2 3 4] forceTo:3 paddingWith:255
+    "
+!
+
 joinWith:separatingElement
     "return a collection generated by concatenating my elements
      and embedding separatingElement in between.
@@ -682,6 +672,12 @@
     "                                     
 !
 
+removeAt:index
+    ^ self removeIndex:index.
+
+    "Created: / 01-07-2018 / 00:55:23 / Claus Gittinger"
+!
+
 shuffled
     "return a randomly shuffled copy of the receiver"
 
@@ -803,17 +799,16 @@
     "
 !
 
-at:index ifAbsent:exceptionBlock
+at:index ifAbsent:exceptionValue
     "return the element at index if valid.
-     If the index is invalid, return the result of evaluating
-     the exceptionblock.
+     If the index is invalid, return the result from exceptionValue.
      NOTICE:
-	in ST-80, this message is only defined for Dictionaries,
-	however, having a common protocol with indexed collections
-	often simplifies things."
+        in ST-80, this message is only defined for Dictionaries,
+        however, having a common protocol with indexed collections
+        often simplifies things."
 
     (index between:1 and:self size) ifFalse:[
-	^ exceptionBlock value
+        ^ exceptionValue value
     ].
     ^ self at:index
 
@@ -823,9 +818,11 @@
      #(1 2 3) at:4 ifAbsent:['no such index']
 
      (Dictionary with:(#foo -> #bar)
-		 with:(#frob -> #baz))
-	 at:#foobar ifAbsent:['no such index']
-    "
+                 with:(#frob -> #baz))
+         at:#foobar ifAbsent:['no such index']
+    "
+
+    "Modified (comment): / 22-12-2018 / 16:50:39 / Claus Gittinger"
 !
 
 atAllIndices:indexCollection
@@ -842,19 +839,23 @@
 !
 
 atIndex:index
-    "return an element at a given index. This allows for seqentialCollections
-     and orderedDictionaries to be both accessed via a numeric index."
+    "return an element at a given index."
 
     ^ self at:index
 
     "Created: / 08-08-2010 / 00:50:10 / cg"
+    "Modified (comment): / 15-06-2017 / 01:42:27 / mawalch"
+    "Modified (comment): / 22-12-2018 / 16:50:53 / Claus Gittinger"
 !
 
 atIndex:index ifAbsent:absentBlock
-    "return an element at a given index. This allows for seqenveableCollections
-     and orderedDictionaries to be both accessed via a numeric index."
+    "return an element at a given index.
+     If the index is invalid, return the value from absentBlock"
 
     ^ self at:index ifAbsent:absentBlock
+
+    "Modified (comment): / 15-06-2017 / 01:43:09 / mawalch"
+    "Modified (comment): / 22-12-2018 / 16:50:12 / Claus Gittinger"
 !
 
 atIndex:index put:newValue
@@ -864,6 +865,36 @@
     ^ self at:index put:newValue
 
     "Created: / 08-08-2010 / 00:50:27 / cg"
+    "Modified (comment): / 15-06-2017 / 01:43:25 / mawalch"
+!
+
+atLastIndex:index
+    "return an element at a given index, counting index from the end."
+
+    ^ self at:(self size + 1 - index)
+
+    "
+     #(10 20 30 40) atLastIndex:1
+     #(10 20 30 40) atLastIndex:4
+     #(10 20 30 40) atLastIndex:5
+    "
+
+    "Created: / 22-12-2018 / 16:49:35 / Claus Gittinger"
+!
+
+atLastIndex:index ifAbsent:exceptionValue
+    "return an element at a given index, counting index from the end.
+     If the index is invalid, return the value from absentBlock"
+
+    ^ self at:(self size + 1 - index) ifAbsent:exceptionValue
+
+    "
+     #(10 20 30 40) atLastIndex:1 ifAbsent:nil
+     #(10 20 30 40) atLastIndex:4 ifAbsent:nil
+     #(10 20 30 40) atLastIndex:5 ifAbsent:nil
+    "
+
+    "Created: / 22-12-2018 / 16:51:07 / Claus Gittinger"
 !
 
 before:anObject
@@ -931,7 +962,7 @@
      No longer raises an error if there are not enough elements;
      instead, returns what is there"
 
-    n < 0 ifTrue:[self error:'bad (negative) argument'].
+    n < 0 ifTrue:[ArgumentError raiseErrorString:'bad (negative) argument'].
 
     "/ OLD:
     "/ "error if collection has not enough elements"
@@ -949,6 +980,22 @@
      #(1 2 3 4 5) asSet first:3
      'hello world' first:5
     "
+
+    "Modified: / 06-06-2019 / 23:23:58 / Claus Gittinger"
+!
+
+firstOrNil
+    "return the first element or nil, if the collection is empty."
+
+    self isEmpty ifTrue:[^ nil].
+    ^ self at:1
+
+    "
+     args:
+     returns: firstElement <object>
+    "
+
+    "Created: / 13-12-2017 / 23:09:37 / stefan"
 !
 
 indexOfNth:n occurrenceOf:what
@@ -975,34 +1022,80 @@
 
 keyAtEqualValue:value
     "return the index of a value.
-     This is normally not used (use indexOf:), but makes the
-     protocol more compatible with dictionaries."
+     This is normally not used (use indexOf:), 
+     but makes the protocol more compatible with dictionaries.
+     This is a slow access, since the receiver is searched sequentially.
+     NOTICE:
+        The value is searched using equality compare"
 
     ^ self indexOf:value
+
+    "Modified (comment): / 07-02-2017 / 11:10:10 / cg"
 !
 
 keyAtEqualValue:value ifAbsent:exceptionBlock
     "return the index of a value.
-     This is normally not used (use indexOf:), but makes the
-     protocol more compatible with dictionaries."
+     This is normally not used (use indexOf:), 
+     but makes the protocol more compatible with dictionaries.
+     This is a slow access, since the receiver is searched sequentially.
+     NOTICE:
+        The value is searched using equality compare"
 
     ^ self indexOf:value ifAbsent:exceptionBlock
+
+    "Modified (comment): / 07-02-2017 / 11:10:03 / cg"
+!
+
+keyAtIdenticalValue:value
+    "return the identity index of a value.
+     This is normally not used (use indexOf:), 
+     but makes the protocol more compatible with dictionaries.
+     This is a slow access, since the receiver is searched sequentially."
+
+    ^ self identityIndexOf:value
+
+    "Created: / 07-02-2017 / 11:10:43 / cg"
+!
+
+keyAtIdenticalValue:value ifAbsent:exceptionBlock
+    "return the identity index of a value.
+     This is normally not used (use indexOf:), 
+     but makes the protocol more compatible with dictionaries.
+     This is a slow access, since the receiver is searched sequentially.
+     NOTICE:
+        The value is searched using identity compare"
+
+    ^ self identityIndexOf:value ifAbsent:exceptionBlock
+
+    "Created: / 07-02-2017 / 11:10:59 / cg"
 !
 
 keyAtValue:value
     "return the index of a value.
-     This is normally not used (use indexOf:), but makes the
-     protocol more compatible with dictionaries."
+     This is normally not used (use indexOf:), 
+     but makes the protocol more compatible with dictionaries.
+     This is a slow access, since the receiver is searched sequentially.
+     NOTICE:
+        The value is searched using identity compare;
+        use #keyAtEqualValue: to compare for equality."
 
     ^ self identityIndexOf:value
+
+    "Modified (comment): / 07-02-2017 / 11:09:43 / cg"
 !
 
 keyAtValue:value ifAbsent:exceptionBlock
     "return the index of a value.
-     This is normally not used (use indexOf:), but makes the
-     protocol more compatible with dictionaries."
+     This is normally not used (use indexOf:), 
+     but makes the protocol more compatible with dictionaries.
+     This is a slow access, since the receiver is searched sequentially.
+     NOTICE:
+        The value is searched using identity compare;
+        use #keyAtEqualValue:ifAbsent: to compare for equality."
 
     ^ self identityIndexOf:value ifAbsent:exceptionBlock
+
+    "Modified (comment): / 07-02-2017 / 11:04:31 / cg"
 !
 
 last
@@ -1028,7 +1121,7 @@
      No longer raises an error if there are not enough elements;
      instead, returns what is there."
 
-    n < 0 ifTrue:[self error:'bad (negative) argument'].
+    n < 0 ifTrue:[ArgumentError raiseErrorString:'bad (negative) argument'].
     "/ OLD:
     "/ n > self size ifTrue:[^ self notEnoughElementsError].
 
@@ -1041,6 +1134,8 @@
      'hello world' last:5
      'hello' last:10
     "
+
+    "Modified: / 06-06-2019 / 23:24:02 / Claus Gittinger"
 !
 
 nth:n
@@ -1112,6 +1207,16 @@
     self at:index2 put:t
 
     "Modified: 15.10.1997 / 19:27:08 / cg"
+!
+
+swapIndex:i1 and:i2
+    "spap element at i1 and i2"
+
+    <resource: #obsolete>
+
+    self swap:i1 with:i2
+
+    "Created: / 17-07-2017 / 10:35:19 / cg"
 ! !
 
 !SequenceableCollection methodsFor:'adding & removing'!
@@ -1169,7 +1274,7 @@
 
 addAll:aCollection beforeIndex:index
     "insert all elements of the argument, anObject to become located at index.
-     The collection may be unordered, but then order of the sliced-in elements
+     The collection may be unordered, but then the order of the sliced-in elements
      is undefined.
      Return the receiver."
 
@@ -1480,7 +1585,8 @@
 !
 
 removeIndex:index
-    "remove the argument stored at index. Return the receiver.
+    "remove the argument stored at index. 
+     Returns the receiver.
 
      Notice that this modifies the receiver, NOT a copy.
      Also note that it may be a slow operation for some collections,
@@ -1494,6 +1600,8 @@
      #(1 2 3 4 5) asOrderedCollection removeIndex:6
      #($a $b $c $d $e $f $g) removeIndex:3
     "
+
+    "Modified (comment): / 24-06-2019 / 12:48:18 / Claus Gittinger"
 !
 
 removeLast
@@ -1543,8 +1651,7 @@
     self combinationsStartingAt:1 prefix:#() do:aBlock
 
     "
-     (Array 
-            with:($a to:$d)) 
+     (Array with:($a to:$d)) 
         combinationsDo:[:eachCombination | Transcript showCR: eachCombination]
     "
     "
@@ -1568,6 +1675,8 @@
             with:#(A)) 
         combinationsDo:[:eachCombination | Transcript showCR: eachCombination]
     "
+
+    "Modified (comment): / 29-08-2017 / 15:34:45 / cg"
 !
 
 combinationsStartingAt:anInteger prefix:prefix do:aBlock
@@ -1908,7 +2017,7 @@
     "return the common prefix of myself and the argument, aCollection.
      If there is none, an empty collection is returned."
 
-    ^ self commonPrefixWith:aCollection ignoreCase:false
+    ^ self commonPrefixWith:aCollection caseSensitive:true
 
     "
      'hello' commonPrefixWith:'hello'
@@ -1931,6 +2040,8 @@
      'ababab' commonPrefixWith:'abcd'
      'abcdef' commonPrefixWith:'abcd'
     "
+
+    "Modified: / 31-03-2017 / 18:01:08 / stefan"
 !
 
 commonPrefixWith:aCollection caseSensitive:caseSensitive
@@ -2016,7 +2127,7 @@
     "return the common suffix (tail) of myself and the argument, aCollection.
      If there is none, an empty collection is returned."
 
-    ^ self commonSuffixWith:aCollection ignoreCase:false
+    ^ self commonSuffixWith:aCollection caseSensitive:true
 
     "
      'hello' commonSuffixWith:'hello'
@@ -2041,6 +2152,8 @@
      'bababa' commonSuffixWith:'dcba'
      'fdcba' commonSuffixWith:'dcba'
     "
+
+    "Modified: / 31-03-2017 / 18:01:21 / stefan"
 !
 
 commonSuffixWith:aCollection caseSensitive:caseSensitive
@@ -2154,6 +2267,41 @@
     ^ 0
 !
 
+compareWith:aSequenceableCollection using:compareBlock
+    "Compare the receiver with the argument and return 1 if the receiver is
+     greater, 0 if equal and -1 if less than the argument.
+     Uses compareBlock on each element, which ought to return -1,0 or 1 when
+     comparing individual elements"
+
+    |mySize    "{ Class: SmallInteger }"
+     otherSize "{ Class: SmallInteger }"
+     n         "{ Class: SmallInteger }"
+     e1 e2 cmp|
+
+    mySize := self size.
+    otherSize := aSequenceableCollection size.
+    n := mySize min:otherSize.
+
+    1 to:n do:[:index |
+        e1 := self at:index.
+        e2 := aSequenceableCollection at:index.
+        cmp := compareBlock value:e1 value:e2.
+        cmp ~~ 0 ifTrue:[
+            "identity compare is faster"    
+            ^ cmp
+        ].
+    ].
+    mySize > otherSize ifTrue:[^ 1].
+    mySize < otherSize ifTrue:[^ -1].
+    ^ 0
+
+    "
+     #(1 2 1.1 2.9 4) compareWith:#(1 2 1 3 4) using:[:a :b | a rounded compareWith:b rounded].
+    "
+
+    "Created: / 29-06-2018 / 11:30:21 / Claus Gittinger"
+!
+
 deepSameContentsAs:aCollection
     "return true, if the receiver and the arg have the same contents
      in both the named instance vars and any indexed instVars.
@@ -2218,6 +2366,40 @@
     "
 !
 
+endsWith:aCollection using:compareBlock
+    "return true, if the receiver's last elements match those of aCollection,
+     using compareBlock to compare individual elements.
+     compareBlock should return true if elements are considered the same.
+     If aCollection is empty, true is returned (incompatible to some other dialect's endsWith.)"
+
+    |index1 "{ Class: SmallInteger }"
+     index2 "{ Class: SmallInteger }"
+     stop   "{ Class: SmallInteger }"
+     sz     "{ Class: SmallInteger }"|
+
+    (aCollection == self) ifTrue:[^ true].
+    (aCollection isSequenceable) ifFalse:[^ false].
+
+    stop := aCollection size.
+    sz := self size.
+    stop > sz ifTrue:[^false].
+
+    index1 := sz.
+    index2 := stop.
+    [index2 > 0] whileTrue:[
+        (compareBlock value:(self at:index1) value:(aCollection at:index2)) ifFalse:[^ false].
+        index1 := index1 - 1.
+        index2 := index2 - 1
+    ].
+    ^ true
+
+    "
+     'abcde' endsWith:#($d $e) using:[:a :b | a asLowercase = b asLowercase]
+    "
+
+    "Created: / 29-06-2018 / 11:36:25 / Claus Gittinger"
+!
+
 endsWithAnyOf:aCollectionOfCollections
     "return true, if the receiver endswith any in aCollection"
 
@@ -2273,6 +2455,23 @@
     "Modified: / 27.3.1998 / 17:33:49 / cg"
 !
 
+indexOfFirstDifferenceWith:anotherCollection
+    "return the index of the first element which is different to the corresponding
+     element in anotherCollection. 0 if they are all the same.
+     The comparison is by equality, i.e. using #="
+     
+    ^ self with:anotherCollection findFirst:[:a :b | a ~= b] 
+
+    "
+     'hello' indexOfFirstDifferenceWith:'helLo' 
+     'hello' indexOfFirstDifferenceWith:'hello'   
+     'hello' indexOfFirstDifferenceWith:'hello1'   
+     'hello1' indexOfFirstDifferenceWith:'hello' 
+    "
+
+    "Created: / 31-08-2017 / 20:10:36 / cg"
+!
+
 isSameSequenceAs:otherCollection
     "Answer whether the receiver's size is the same as otherCollection's size,
      and each of the receiver's elements equal the corresponding element of otherCollection.
@@ -2395,8 +2594,7 @@
 !
 
 startsWith:aCollection
-    "return true, if the receiver's first elements match those
-     of aCollection
+    "return true, if the receiver's first elements match those of aCollection
      If the argument is empty, true is returned.
      Notice, that this is similar to, but slightly different from VW's and Squeak's beginsWith:,
      which are both inconsistent w.r.t. an empty argument."
@@ -2426,6 +2624,41 @@
      #(1 2 3 4) asOrderedCollection startsWith:#(1 2 3)
      #(1 2 3 4) asOrderedCollection startsWith:#()
     "
+
+    "Modified (comment): / 12-02-2017 / 11:19:40 / cg"
+!
+
+startsWith:aCollection using:compareBlock
+    "return true, if the receiver's first elements match those of aCollection,
+     using compareBlock to compare individual elements.
+     compareBlock should return true if elements are considered the same.
+     If the argument is empty, true is returned.
+     Notice, that this is similar to, but slightly different from VW's and Squeak's beginsWith:,
+     which are both inconsistent w.r.t. an empty argument."
+
+    |index "{ Class: SmallInteger }"
+     stop  "{ Class: SmallInteger }" |
+
+    (aCollection == self) ifTrue:[^true].
+    (aCollection isSequenceable) ifFalse:[^false].
+
+    stop := aCollection size.
+    stop > self size ifTrue:[^false].
+
+    index := 1.
+    [index <= stop] whileTrue:[
+        (compareBlock value:(self at:index) value:(aCollection at:index)) ifFalse:[^false].
+        index := index + 1
+    ].
+    ^ true
+
+    "
+     'aBCde' startsWith:'abc' using:[:a :b | a asLowercase = b asLowercase]
+     'abCde' startsWith:'abc' using:[:a :b | a asLowercase = b asLowercase]
+     'axCde' startsWith:'abc' using:[:a :b | a asLowercase = b asLowercase]
+    "
+
+    "Created: / 29-06-2018 / 11:36:38 / Claus Gittinger"
 !
 
 startsWithAnyOf:aCollectionOfCollections
@@ -2473,40 +2706,12 @@
 
 !SequenceableCollection methodsFor:'converting'!
 
-asCollectionOfSubCollectionsOfSize:pieceSize
-    "slice into pieces; return a collection containing pieces of size pieceSize from the receiver.
-     The last piece may be smaller, if the receiver's size is not a multiple of pieceSize."
-
-    |pieces
-     start  "{ Class:SmallInteger }"
-     stop   "{ Class:SmallInteger }"
-     mySize "{ Class:SmallInteger }"|
-
-    pieces := self speciesForSubcollection new.
-    start := 1. stop := start + pieceSize - 1.
-    mySize := self size.
-    [stop <= mySize] whileTrue:[
-        pieces add:(self copyFrom:start to:stop).
-        start := start + pieceSize.
-        stop := stop + pieceSize.
-    ].
-    (start <= mySize) ifTrue:[
-        pieces add:(self copyFrom:start to:mySize).
-    ].
-    ^ pieces
-
-    "
-     '123123123123123123' asCollectionOfSubCollectionsOfSize:3 
-     '12312312312312312312' asCollectionOfSubCollectionsOfSize:3 
-    "
-
-    "Modified: / 24-01-2017 / 18:55:07 / stefan"
-!
-
 asCollectionOfSubCollectionsSeparatedBy:anElement
     "return a collection containing the subcollections (separated by anElement)
      of the receiver. If anElement occurs multiple times in a row,
      the result will contain empty collections.
+     If the receiver starts with anElement, an initial empty collection is added. 
+     If the receiver ends with anElement, NO final empty collection is added. 
      This algorithm uses equality-compare to detect the element."
 
     |cols myClass
@@ -2541,73 +2746,21 @@
      #(a b c d e f g h) asCollectionOfSubCollectionsSeparatedBy: #d. 
      #(a b c d e f d d g h) asCollectionOfSubCollectionsSeparatedBy: #d.
      'foo-bar-baz' asCollectionOfSubCollectionsSeparatedBy: $-.
+     '-foo-bar-baz' asCollectionOfSubCollectionsSeparatedBy: $-.
+     'foo-bar-baz-' asCollectionOfSubCollectionsSeparatedBy: $-.
+     '-foo-bar-baz-' asCollectionOfSubCollectionsSeparatedBy: $-.
      'foobarbaz' asCollectionOfSubCollectionsSeparatedBy: $-. 
      '' asCollectionOfSubCollectionsSeparatedBy: $-. 
     "
 
     "Modified (format): / 24-01-2017 / 18:55:53 / stefan"
-!
-
-asCollectionOfSubCollectionsSeparatedBy:anElement do:aBlock
-    "evaluate aBlock for each subcollection generated by separating elements
-     of the receiver by anElement.
-     If anElement occurs multiple times in a row,
-     the block will be invoked with empty collections as argument.
-     This algorithm uses equality-compare to detect the element."
-
-    |subCollection
-     endIndex      "{ Class:SmallInteger }"
-     startIndex    "{ Class:SmallInteger }"
-     stopIndex     "{ Class:SmallInteger }" |
-
-    startIndex := 0.
-    endIndex := self size.
-
-    [startIndex <= endIndex] whileTrue:[
-        stopIndex := self indexOf:anElement startingAt:startIndex+1.
-        stopIndex == 0 ifTrue:[
-            stopIndex := self size
-        ] ifFalse: [
-            stopIndex := stopIndex - 1.
-        ].
-
-        (stopIndex < startIndex) ifTrue: [
-            subCollection := self species new:0
-        ] ifFalse: [
-            subCollection := self copyFrom:startIndex+1 to:stopIndex
-        ].
-        aBlock value:subCollection.
-        startIndex := stopIndex + 1
-    ].
-
-    "
-     '' 
-        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
-
-     '1 one' 
-        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
-
-     '1 one:2 two:3 three:4 four:5 five' 
-        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
-
-     'a::b' 
-        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
-
-     ':' 
-        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
-
-     ':a' 
-        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
-
-     'a:' 
-        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
-    "
+    "Modified (comment): / 11-02-2019 / 23:45:11 / Claus Gittinger"
 !
 
 asCollectionOfSubCollectionsSeparatedByAll:aSeparatorCollection
     "return a collection containing the subcollections (separated by aSeparatorCollection)
      of the receiver. If aSeparatorCollection occurs multiple times in a row,
-     the result will contain empty strings.
+     the result may contain empty strings.
      Uses equality-compare when searching for aSeparatorCollection."
 
     |items done myClass
@@ -2639,70 +2792,13 @@
 
     "
      '1::2::3::4::5::' asCollectionOfSubCollectionsSeparatedByAll:'::'
+     '::2' asCollectionOfSubCollectionsSeparatedByAll:'::'
      #(1 2 3 1 2 3 4 3 1 1 2 3 1 4 5) asCollectionOfSubCollectionsSeparatedByAll:#(3 1)
      'hello+#world+#here' asCollectionOfSubCollectionsSeparatedByAll:'+#'
     "
 
     "Modified (comment): / 24-01-2017 / 18:57:03 / stefan"
-!
-
-asCollectionOfSubCollectionsSeparatedByAny:aCollectionOfSeparators
-    "return a collection containing the subCollection
-     (separated by any from aCollectionOfSeparators) of the receiver.
-     This allows breaking up strings using a number of elements as separator.
-     Uses equality-compare when searching for separators."
-
-    ^ self asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:el | aCollectionOfSeparators includes:el]
-
-    "
-     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAny:#($:)
-     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAny:':'
-     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAny:(Array with:$: with:Character space)
-     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAny:': '
-     'h1e2l3l4o' asCollectionOfSubCollectionsSeparatedByAny:($1 to: $9)
-     #(1 9 2 8 3 7 4 6 5 5) asCollectionOfSubCollectionsSeparatedByAny:#(1 2 3)
-    "
-!
-
-asCollectionOfSubCollectionsSeparatedByAnyForWhich:aBlock
-    "return a collection containing the subCollection
-     (separated by elements for which aBlock evaluates to true) of the receiver.
-     This allows breaking up strings using an arbitrary condition."
-
-    |words
-     start  "{ Class:SmallInteger }"
-     stop   "{ Class:SmallInteger }"
-     mySize "{ Class:SmallInteger }"|
-
-    words := self speciesForSubcollection new.
-    start := 1.
-    mySize := self size.
-    [start <= mySize] whileTrue:[
-        "skip multiple separators"
-        [ aBlock value:(self at:start)] whileTrue:[
-            start := start + 1 .
-            start > mySize ifTrue:[
-                ^ words
-            ].
-        ].
-
-        stop := self findFirst:aBlock startingAt:start.
-        stop == 0 ifTrue:[
-            words add:(self copyFrom:start to:mySize).
-            ^ words
-        ].
-        words add:(self copyFrom:start to:(stop - 1)).
-        start := stop
-    ].
-    ^ words
-
-    "
-     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:ch | ch = $:]
-     'h1e2l3l4o' asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:ch | ch isDigit]
-     #(1 9 2 8 3 7 4 6 5 5) asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:n | n odd]
-    "
-
-    "Modified (format): / 24-01-2017 / 18:57:57 / stefan"
+    "Modified (comment): / 03-07-2018 / 11:00:24 / Claus Gittinger"
 !
 
 asCollectionOfSubCollectionsSeparatedByAnyForWhich:aBlock withSeparatorsIncluded:aBoolean
@@ -2753,6 +2849,19 @@
     "Created: / 29-05-2018 / 13:58:54 / svestkap"
 !
 
+asKeysAndValues
+    "return a new OrderedDictionary with the receiver collection's elements,
+     which must be associations"
+
+    ^ OrderedDictionary withAssociations:self.
+
+    "
+     { 'ten' -> 10 . 'twenty' -> 20 . 'thirty' -> 30 } asKeysAndValues 
+    "
+
+    "Created: / 14-09-2018 / 18:00:58 / Stefan Vogel"
+!
+
 asSequenceableCollection
     "return myself as a SequenceableCollection.
      I am already a SequenceableCollection."
@@ -2766,173 +2875,68 @@
     "return a new string collection containing the elements;
      these ought to be strings. (i.e. String or Text instances)"
 
-    |newColl sz|
+    |sz|
 
     sz := self size.
-    newColl := StringCollection newWithSize:sz.
-    newColl replaceFrom:1 to:sz with:self startingAt:1.
-    ^ newColl
-
-    "Created: 18.5.1996 / 13:53:55 / cg"
-    "Modified: 18.5.1996 / 14:00:16 / cg"
-!
-
-asStringWith:sepCharOrString
-    "return a string generated by concatenating my elements
-     (which must be strings or nil) and embedding sepCharOrString characters in between.
-     The argument sepCharOrString may be a character, a string or nil.
-     Nil entries and empty strings are counted as empty lines.
-     Similar to joinWith:, but specifically targeted towards collections of strings."
-
-    ^ self
-        from:1 to:(self size)
-        asStringWith:sepCharOrString
-        compressTabs:false
-        final:nil
-
-    "
-     #('hello' 'world' 'foo' 'bar' 'baz') asStringWith:$;
-     #('hello' 'world' 'foo' 'bar' 'baz') asStringWith:'|'
-     'hello|world|foo|bar|baz' asCollectionOfSubstringsSeparatedBy:$|
-    "
-
-    "Modified: / 10-07-2010 / 22:59:29 / cg"
-!
-
-asStringWith:sepCharacterOrString from:firstLine to:lastLine
-    "return part of myself as a string with embedded sepCharacters.
-     My elements must be strings or nil; nil entries and empty strings are
-     taken as empty lines.
-     The argument sepCharOrString may be a character, a string or nil.
-     Similar to joinWith:, but specifically targeted towards collections of strings."
-
-    ^ self
-        from:firstLine to:lastLine
-        asStringWith:sepCharacterOrString
-        compressTabs:false
-        final:nil
-    "
-     creating entries for searchpath:
-
-     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$;
-
-     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$: from:1 to:3
-    "
-
-    "Modified: 23.2.1996 / 15:28:55 / cg"
-!
-
-asStringWith:sepCharacterOrString from:firstLine to:lastLine compressTabs:compressTabs final:endCharacterOrString
-    "return part of myself as a string or text with embedded sepCharacters.
-     My elements must be strings or nil; nil entries and empty strings are
-     taken as empty lines.
-     The arguments sepCharacterOrString and endCharacterOrString may be nil, a character or a string.
-     If the argument compressTabs is true, leading spaces are converted
-     to tab-characters (8col tabs). The last line is followed by a final
-     character (if non-nil).
-     Similar to joinWith:, but specifically targeted towards collections of strings."
-
-    ^ self
-        from:firstLine to:lastLine
-        asStringWith:sepCharacterOrString
-        compressTabs:compressTabs
-        final:endCharacterOrString
-        withEmphasis:true
-
-    "Modified: / 17.6.1998 / 12:31:19 / cg"
-!
-
-asStringWith:sepCharacterOrString from:firstLine to:lastLine compressTabs:compressTabs final:endCharacterOrString withEmphasis:withEmphasis
-    "return part of myself as a string or text with embedded sepCharacters
-     and followup endCharacter.
-     My elements must be strings or nil; nil entries and empty strings are
-     taken as empty lines.
-     The arguments sepCharacterOrString and endCharacterOrString may be nil, a character or a string.
-     If the argument compressTabs is true, leading spaces are converted
-     to tab-characters (8col tabs). The last line is followed by a final
-     character (if non-nil).
-     The withEmphais argument controls if the returned string should preserve
-     any emphasis. If false, a plain string is returned.
-     This method is tuned for big collections, in not creating many
-     intermediate strings (has linear runtime). For very small collections
-     and small strings, it may be faster to use the comma , operation.
-     Similar to joinWith:, but specifically targeted towards collections of strings."
-
-    ^ self
-        from:firstLine to:lastLine
-        asStringWith:sepCharacterOrString
-        compressTabs:compressTabs
-        final:endCharacterOrString
-        withEmphasis:withEmphasis
-!
-
-asStringWithCRs
-    "return a string generated by concatenating my elements
-     (which must be strings or nil) and embedding cr characters in between.
-     Nil entries and empty strings are counted as empty lines."
-
-    ^ self asStringWithCRsFrom:1 to:(self size)
-
-    "
-     #('hello' 'world' 'foo' 'bar' 'baz') asStringWithCRs
-
-     (OrderedCollection new
-	add:'hello';
-	add:'world';
-	add:'foo';
-	add:('bar' asText allBold);
-	yourself) asStringWithCRs
-
-     Transcript showCR:
-	 (OrderedCollection new
-	    add:'hello';
-	    add:'world';
-	    add:'foo';
-	    add:('bar' asText allBold);
-	    yourself) asStringWithCRs
-    "
-
-    "Modified: 18.5.1996 / 16:43:47 / cg"
-!
-
-asStringWithCRsFrom:firstLine to:lastLine
-    "return a string generated by concatenating some of my elements
-     (which must be strings or nil) and embedding cr characters in between.
-     Nil entries and empty strings are counted as empty lines."
-
-    ^ self asStringWithCRsFrom:firstLine to:lastLine compressTabs:false withCR:true
-
-    "
-     #('hello' 'world' 'foo' 'bar' 'baz') asStringWithCRsFrom:2 to:4
-
-    "
-
-    "Modified: 18.5.1996 / 16:50:55 / cg"
-!
-
-asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs
-    "return part of myself as a string with embedded cr's.
-     My elements must be strings or nil.
-     If the argument compressTabs is true, leading spaces are converted
-     to tab-characters (8col tabs).
-     Nil entries and empty strings are taken as empty lines."
-
-    ^ self asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs withCR:true
-!
-
-asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs withCR:withCR
-    "return part of myself as a string with embedded cr's.
-     My elements must be strings or nil; nil entries and empty strings are
-     taken as empty lines.
-     If the argument compressTabs is true, leading spaces are converted
-     to tab-characters (8col tabs). WithCR controls whether the last line
-     should be followed by a cr or not."
+    ^ (StringCollection newWithSize:sz)
+        replaceFrom:1 to:sz with:self startingAt:1;
+        yourself.
+
+    "Created: / 18-05-1996 / 13:53:55 / cg"
+    "Modified: / 09-10-2017 / 17:05:19 / stefan"
+!
+
+asStringWithoutEmphasis
+    "return myself as a string with embedded cr's, but drop any emphasis"
 
     ^ self 
-        asStringWith:(Character cr)
-        from:firstLine to:lastLine
-        compressTabs:compressTabs
-        final:(withCR ifTrue:[Character cr] ifFalse:[nil])
+        asStringWith:Character cr
+        from:1 to:(self size) 
+        compressTabs:false 
+        final:Character cr
+        withEmphasis:false
+
+    "Created: / 17.6.1998 / 12:32:48 / cg"
+!
+
+asVersionNumberCollection
+    "Convert a collection of strings or numbers to a version number.
+     Remove zeroes from the end."
+
+    |coll trailingZerosCount|
+
+    coll := self collect:[:each| each isInteger 
+                                        ifTrue:[each] 
+                                        ifFalse:[Integer readFromString:each onError:each]
+                            ] as:Array.
+
+    coll last == 0 ifTrue:[
+        trailingZerosCount := 0.
+        coll reversed doWhileTrue:[:each |
+            each == 0 ifTrue:[
+                trailingZerosCount := trailingZerosCount + 1.
+                true.
+            ] ifFalse:[
+                false
+            ].
+        ].
+
+        trailingZerosCount ~~ 0 ifTrue:[
+            coll := coll copyTo:coll size - trailingZerosCount
+        ].
+    ].
+
+    ^ coll
+
+   "
+     #(1) asVersionNumberCollection.
+     #(1 '1') asVersionNumberCollection.
+     #(1 '1a') asVersionNumberCollection.
+     #(1 1 0) asVersionNumberCollection.
+     #('expecco' 18 10) asVersionNumberCollection.
+    "
+
+    "Created: / 20-06-2018 / 17:33:26 / Stefan Vogel"
 !
 
 decodeAsLiteralArray
@@ -2989,52 +2993,6 @@
     "Modified: / 26-03-2007 / 13:57:10 / cg"
 !
 
-from:firstLine to:lastLine asStringWith:sepCharacterOrString
-    "return part of myself as a string with embedded sepCharacterOrStrings.
-     The argument sepCharacterOrString may be a character, a string or nil.
-     My elements must be strings or nil; nil entries and empty strings are
-     taken as empty lines."
-
-    ^ self
-        from:firstLine
-        to:lastLine
-        asStringWith:sepCharacterOrString
-        compressTabs:false
-        final:nil
-    "
-     creating entries for searchpath:
-
-     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$;
-
-     #('foo' 'bar' 'baz' '/foo/bar') from:1 to:3 asStringWith:$:
-
-     (#('foo' 'bar' 'baz' '/foo/bar') copyFrom:1 to:3) asStringWith:$:
-    "
-
-    "Modified: 23.2.1996 / 15:28:55 / cg"
-!
-
-from:firstLine to:lastLine asStringWith:sepCharacterOrString compressTabs:compressTabs final:endCharacterOrString
-    "return part of myself as a string or text with embedded sepCharacters.
-     My elements must be strings or nil; nil entries and empty strings are
-     taken as empty lines.
-     The arguments sepCharacterOrString and endCharacterOrString may be characters,
-     strings or nil.
-     If the argument compressTabs is true, leading spaces are converted
-     to tab-characters (8col tabs). 
-     The last line is followed by a final character (if non-nil)."
-
-    ^ self
-        from:firstLine
-        to:lastLine
-        asStringWith:sepCharacterOrString 
-        compressTabs:compressTabs
-        final:endCharacterOrString 
-        withEmphasis:true
-
-    "Modified: / 17.6.1998 / 12:31:19 / cg"
-!
-
 from:firstLine to:lastLine asStringWith:sepCharacterOrString compressTabs:compressTabs final:endCharacterOrString withEmphasis:withEmphasis
     "return part of myself as a string or text with embedded sepCharacterOrString
      and followup endCharacterOrString.
@@ -3055,7 +3013,7 @@
      totalLength "{ Class:SmallInteger }"
      pos         "{ Class:SmallInteger }"
      sepCnt      "{ Class:SmallInteger }"
-     newString lineString spaces idx nTabs
+     newString lineString idx nTabs
      maxBitsPerCharacter stringClass needEmphasis newRuns c
      thisLen anyTab|
 
@@ -3083,8 +3041,8 @@
     idx2 := lastLine.
     idx1 to:idx2 do:[:lineIndex |
         lineString := self at:lineIndex.
-
         lineString notNil ifTrue:[
+            lineString := lineString asString.
             withEmphasis ifTrue:[
                 lineString hasChangeOfEmphasis ifTrue:[
                     needEmphasis := true
@@ -3116,7 +3074,6 @@
     ].
     totalLength <= 0 ifTrue:[^ ''].
 
-    spaces := '        '.
     newString := stringClass new:totalLength.
 
     needEmphasis ifTrue:[
@@ -3132,6 +3089,9 @@
     pos := 1.
     idx1 to:idx2 do:[:lineIndex |
         lineString := self at:lineIndex.
+        lineString notNil ifTrue:[
+            lineString := lineString asString.
+        ].
         thisLen := lineString size.
         thisLen ~~ 0 ifTrue:[
             withEmphasis ifFalse:[
@@ -3288,89 +3248,24 @@
 
     "
 
-    "Created: / 17.6.1998 / 12:30:32 / cg"
-    "Modified: / 17.6.1998 / 12:31:59 / cg"
-!
-
-joinWithAll:separatingCollection
-    "return a collection generated by concatenating my elements
-     and slicing separatingCollection in between.
-     Similar to asStringWith:, but not specifically targeted towards collections of strings."
-
-    ^ self
-        joinWithAll:separatingCollection
-        from:1 to:(self size) as:nil
-
-    "
-     #('hello' 'world' 'foo' 'bar' 'baz') joinWithAll:' ; '   
-     #('hello' 'world' 'foo' 'bar' 'baz') joinWithAll:' | '
-    "
-!
-
-joinWithAll:separatingCollection from:startIndex to:endIndex as:speciesOrNil 
-    "extract parts of myself as a new collection with optional embedded separator.
-     Separator may be nil, or a collection of elements to be sliced in between.
-     SpeciesOrNil specifies the species of the resultig object, allowing for Arrays to be converted
-     as OrderedCollection or vice versa on the fly. If nil is passed in, the species of the first non-nil
-     element is used.
-     This counts the overall size first, then allocates the new collection once and replaces elements
-     via bulk copies. For very small collections, it may be faster to use the comma , operation.
-     Similar to asStringWith:, but not specifically targeted towards string handling."
-
-    |totalLength "{ Class:SmallInteger }"
-     pos         "{ Class:SmallInteger }"
-     sepCnt      "{ Class:SmallInteger }"
-     subColl newColl 
-     species|
-
-    startIndex = endIndex ifTrue:[ ^ self at:startIndex ].
-
-    species := speciesOrNil.
-
-    "
-     first accumulate the size of the result, 
-     to avoid countless reallocations.
-    "
-    totalLength := 0.
-    sepCnt := separatingCollection size.
-
-    startIndex to:endIndex do:[:index |
-        subColl := self at:index.
-        totalLength := totalLength + subColl size.
-        species isNil ifTrue:[
-            subColl notNil ifTrue:[
-                species := subColl species
-            ]
-        ]
-    ].
-    totalLength := totalLength + ((endIndex - startIndex) * sepCnt).
-    newColl := species newWithSize:totalLength.
-
-    pos := 1.
-    startIndex to:endIndex do:[:index |
-        subColl := self at:index.
-        subColl size ~~ 0 ifTrue:[
-            newColl replaceFrom:pos with:subColl startingAt:1.
-            pos := pos + subColl size.
-        ].
-        ((sepCnt ~~ 0) and:[index ~~ endIndex]) ifTrue:[
-            newColl replaceFrom:pos to:(pos+sepCnt-1) with:separatingCollection startingAt:1.
-            pos := pos + sepCnt.
-        ].
-    ].
-
-    ^ newColl
-
-    "
-     #( 'aa' 'bb' '' 'cc' ) joinWith:'|' from:1 to:4 as:String  
-     #( 'aa' 'bb' '' 'cc' ) joinWith:nil from:1 to:4 as:String  
-     #( 'aa' 'bb' '' 'cc' ) joinWith:'|' from:1 to:4 as:Array   
-     #( (1 2 3) (4 5 6) (7 6 8) ) joinWith:#(nil) from:1 to:3 as:OrderedCollection  
-     #( (1 2 3) (4 5 6) (7 6 8) ) joinWith:nil from:1 to:3 as:nil                
-    "
-
-    "Created: / 17.6.1998 / 12:30:32 / cg"
-    "Modified: / 17.6.1998 / 12:31:59 / cg"
+    "Created: / 17-06-1998 / 12:30:32 / cg"
+    "Modified: / 21-09-2017 / 12:46:43 / stefan"
+    "Modified: / 22-02-2019 / 09:51:42 / Stefan Vogel"
+!
+
+pairsAsDictionary
+    "return a new Dictionary with the receiver collection's elements,
+     each of which must be a SequenceableCollection with two elements"
+
+    ^ OrderedDictionary withKeyValuePairs:self.
+
+    "
+     #( ('ten' 10) ('twenty' 20) ('thirty' 30)) asSet pairsAsDictionary 
+     #( ('ten' 10) ('twenty' 20) ('thirty' 30)) pairsAsDictionary 
+    "
+
+    "Created: / 11-09-2018 / 12:30:16 / Stefan Vogel"
+    "Modified (comment): / 11-09-2018 / 15:37:18 / Stefan Vogel"
 !
 
 splitBy:anElement
@@ -3387,90 +3282,44 @@
      '1 one 2 two 3 three 4 four 5 five' withCRs splitBy:Character space
      #(a b c d e f g h) splitBy: #d.
      #(a b c d e f d d g h) splitBy: #d.
-    "
-!
-
-splitBy:anElement do:aBlock
-    "evaluate aBlock for each subcollection generated by separating elements
-     of the receiver by anElement.
-     If anElement occurs multiple times in a row,
-     the block will be invoked with empty collections as argument.
-     This algorithm uses equality-compare to detect the element."
-
-    ^ self asCollectionOfSubCollectionsSeparatedBy:anElement do:aBlock
-
-    "
-     '' 
-        splitBy:$: do:[:each | Transcript showCR:each storeString]
-
-     '1 one' 
-        splitBy:$: do:[:each | Transcript showCR:each storeString]
-
-     '1 one:2 two:3 three:4 four:5 five' 
-        splitBy:$: do:[:each | Transcript showCR:each storeString]
-
-     'a::b' 
-        splitBy:$: do:[:each | Transcript showCR:each storeString]
-
-     ':' 
-        splitBy:$: do:[:each | Transcript showCR:each storeString]
-
-     ':a' 
-        splitBy:$: do:[:each | Transcript showCR:each storeString]
-
-     'a:' 
-        splitBy:$: do:[:each | Transcript showCR:each storeString]
-    "
+     'a;b;c;d' splitBy: $;.
+    "
+
+    "Modified (comment): / 02-10-2018 / 17:30:21 / Claus Gittinger"
 !
 
 splitByAll:aSeparatorCollection
     "return a collection containing the subcollections (separated by aSeparatorCollection)
      of the receiver. If aSeparatorCollection occurs multiple times in a row,
      the result will contain empty strings.
-     Uses equality-compare when searching for aSeparatorCollection."
+     Uses equality-compare when searching for aSeparatorCollection.
+     More or less the same as spitOn: (but has been around earlier)"
 
     ^ self asCollectionOfSubCollectionsSeparatedByAll:aSeparatorCollection
 
     "
-     '1::2::3::4::5::' splitByAll:'::'
+     '1::2::3::4::5::' splitByAll:'::'   
      #(1 2 3 1 2 3 4 3 1 1 2 3 1 4 5) splitByAll:#(3 1)
     "
-!
-
-splitByAny:aCollectionOfSeparators
-    "return a collection containing the subCollection
-     (separated by any from aCollectionOfSeparators) of the receiver.
-     This allows breaking up strings using a number of elements as separator.
-     Uses equality-compare when searching for separators."
-
-    ^ self asCollectionOfSubCollectionsSeparatedByAny:aCollectionOfSeparators
-
-    "
-     'hello:world:isnt:this nice' splitByAny:#($:)
-     'hello:world:isnt:this nice' splitByAny:':'
-     'hello:world:isnt:this nice' splitByAny:(Array with:$: with:Character space)
-     'hello:world:isnt:this nice' splitByAny:#( $: $ ) 
-     'hello:world:isnt:this nice' splitByAny:{ $: . $ }
-     'hello:world:isnt:this nice' splitByAny:': '
-     'h1e2l3l4o' splitByAny:($1 to: $9)
-     #(1 9 2 8 3 7 4 6 5 5) splitByAny:#(1 2 3)
-    "
-!
-
-splitByAnyForWhich:aBlock
+    "
+     '1::2::3::4::5::' splitOn:'::'
+    "
+!
+
+splitByAnyForWhich:aBlock 
     "return a collection containing the subCollection
      (separated by elements for which aBlock evaluates to true) of the receiver.
      This allows breaking up strings using an arbitrary condition."
-    
-    ^ self asCollectionOfSubCollectionsSeparatedByAnyForWhich:aBlock      
+
+    ^ self asCollectionOfSubCollectionsSeparatedByAnyForWhich:aBlock
 
     "
      'hello:world:isnt:this nice' splitByAnyForWhich:[:ch | ch = $:]
      'h1e2l3l4o' splitByAnyForWhich:[:ch | ch isDigit]
-     #(1 9 2 8 3 7 4 6 5 5 1 2 9) splitByAnyForWhich:[:n | n odd]
-    "
-
-    "Modified (format): / 29-05-2018 / 13:24:06 / svestkap"
+     #(1 9 2 8 3 7 4 6 5 5) splitByAnyForWhich:[:n | n odd]
+    "
+
+    "Modified: / 22-02-2019 / 11:59:30 / Stefan Vogel"
 !
 
 splitByAnyForWhich:aBlock withSeparatorIncluded:aBoolean
@@ -3492,44 +3341,34 @@
     "Created: / 29-05-2018 / 14:01:45 / svestkap"
 !
 
-splitForSize:pieceSize
-    "slice into pieces; return a collection containing pieces of size pieceSize from the receiver.
-     The last piece may be smaller, if the receiver's size is not a multiple of pieceSize."
-
-    ^ self asCollectionOfSubCollectionsOfSize:pieceSize
-
-    "
-     '123123123123123123' splitForSize:3 
-     '12312312312312312312' splitForSize:3 
-    "
-!
-
 subCollections:aBlock 
-    "Answser an ordered collection of ordered collections
+    "Answer an ordered collection of ordered collections
      where each subcollection is delimited by an element of the receiver
      for which the given block evaluates to true."
     
-    |str answer current e|
+    |str answer currentSubCollection currentElement|
 
     str := self readStream.
     answer := OrderedCollection new.
-    current := OrderedCollection new.
+    currentSubCollection := OrderedCollection new.
     [ str atEnd ] whileFalse:[
-        e := str next.
-        current add:e.
-        (aBlock value:e) ifTrue:[
-            answer add:current.
-            current := OrderedCollection new
+        currentElement := str next.
+        currentSubCollection add:currentElement.
+        (aBlock value:currentElement) ifTrue:[
+            answer add:currentSubCollection.
+            currentSubCollection := OrderedCollection new
         ]
     ].
-    current notEmpty ifTrue:[
-        answer add:current
+    currentSubCollection notEmpty ifTrue:[
+        answer add:currentSubCollection
     ].
     ^ answer
 
     "
      #( 1 2 3 nil 4 5 6 nil 7 8 9 nil ) subCollections:[:el | el isNil].
     "
+
+    "Modified (comment): / 17-03-2017 / 18:10:56 / stefan"
 ! !
 
 !SequenceableCollection methodsFor:'converting-reindexed'!
@@ -3541,13 +3380,11 @@
      however, physically, no copy is made).
      Warning:
         The slice SHARES the memory for the element-data with the original,
-        this means that any modifications in the original are visible in the slice
-        and vice versa."
-
-    ^ self
-        from:startIndex
-        to:self size
-        by:1
+        it is like a readOnly pointer INTO the receiver.
+        This means that any modifications in the original are visible in the slice
+        and vice versa (well, no: because the slice is readOnly)."
+
+    ^ self from:startIndex to:(self size) by:1
 
     "
      #(1 2 3 4 5 6 7) from:3
@@ -3555,6 +3392,9 @@
      ( #(1 2 3 4 5 6 7) from:3 ) last
      ( #(1 2 3 4 5 6 7) from:3 ) size
     "
+
+    "Modified (comment): / 22-02-2017 / 10:49:20 / cg"
+    "Modified (comment): / 08-03-2019 / 13:29:39 / Claus Gittinger"
 !
 
 from:startIndex by:step
@@ -3564,8 +3404,9 @@
      however, physically, no copy is made).
      Warning:
         The slice SHARES the memory for the element-data with the original,
-        this means that any modifications in the original are visible in the slice
-        and vice versa."
+        it is like a readOnly pointer INTO the receiver.
+        This means that any modifications in the original are visible in the slice
+        and vice versa (well, no: because the slice is readOnly)."
 
     ^ self
         from:startIndex
@@ -3579,7 +3420,11 @@
      ( #(1 2 3 4 5 6 7) from:3 by:2) first
      ( #(1 2 3 4 5 6 7) from:3 by:2) last
      ( #(1 2 3 4 5 6 7) from:3 by:2) size
-    "
+     ( #(1 2 3 4 5 6 7) from:5 by:-2)
+    "
+
+    "Modified (comment): / 22-02-2017 / 10:51:44 / cg"
+    "Modified (comment): / 08-03-2019 / 13:27:49 / Claus Gittinger"
 !
 
 from:startIndex count:numberOfElements
@@ -3587,12 +3432,13 @@
      in the receiver starting at index start (i.e. reference to a slice).
      Warning:
         The slice SHARES the memory for the element-data with the original,
-        this means that any modifications in the original are visible in the slice
-        and vice versa."
-
-    ^ self
-        from:startIndex
-        to:(startIndex + numberOfElements - 1)
+        it is like a readOnly pointer INTO the receiver.
+        This means that any modifications in the original are visible in the slice
+        and vice versa (well, no: because the slice is readOnly)."
+
+    ^ self 
+        from:startIndex to:(startIndex + numberOfElements - 1)
+        by:1 
 
     "
      #($a $b $c $d $e $f $g) from:2 count:3
@@ -3618,24 +3464,8 @@
      slice at:1 put:40.
      slice.
     "
-!
-
-from:startIndex count:numberOfElements put:newElement
-    "replace numberOfElements elements from startIndex of the collection
-     by the argument, newElement.
-     Notice: This operation modifies the receiver, NOT a copy;
-     therefore the change may affect all others referencing the receiver."
-
-    ^ self
-        from:startIndex
-        to:(startIndex + numberOfElements - 1)
-        put:newElement
-
-    "
-     #($a $b $c $d $e $f $g) copy from:2 count:3 put:nil
-     '1234567890' copy from:2 count:5 put:$*
-     '1234567890' copy from:2 count:20 put:$* -> error
-    "
+
+    "Modified (comment): / 08-03-2019 / 13:29:33 / Claus Gittinger"
 !
 
 from:startIndex to:endIndex
@@ -3645,8 +3475,9 @@
      however, physically, no copy is made).
      Warning:
         The slice SHARES the memory for the element-data with the original,
-        this means that any modifications in the original are visible in the slice
-        and vice versa."
+        it is like a readOnly pointer INTO the receiver.
+        This means that any modifications in the original are visible in the slice
+        and vice versa (well, no: because the slice is readOnly)."
 
     ^ self
         from:startIndex
@@ -3660,7 +3491,15 @@
      ( #(1 2 3 4 5 6 7) from:3 to:6) first
      ( #(1 2 3 4 5 6 7) from:3 to:6) last
      ( #(1 2 3 4 5 6 7) from:3 to:6) size
-    "
+     
+     #(1 2 3 4 5 6 7) from:3 to:1
+     ( #(1 2 3 4 5 6 7) from:3 to:1 ) first
+     ( #(1 2 3 4 5 6 7) from:3 to:1 ) last
+     ( #(1 2 3 4 5 6 7) from:3 to:1 ) size
+    "
+
+    "Modified (comment): / 22-02-2017 / 10:51:06 / cg"
+    "Modified (comment): / 08-03-2019 / 13:28:01 / Claus Gittinger"
 !
 
 from:startIndex to:endIndex by:step
@@ -3670,8 +3509,9 @@
      however, physically, no copy is made).
      Warning:
         The slice SHARES the memory for the element-data with the original,
-        this means that any modifications in the original are visible in the slice
-        and vice versa."
+        it is like a readOnly pointer INTO the receiver.
+        This means that any modifications in the original are visible in the slice
+        and vice versa (well, no: because the slice is readOnly)."
 
     ^ ReindexedCollection
         on:self
@@ -3684,7 +3524,12 @@
      ( #(1 2 3 4 5 6 7) from:3 to:7 by:2) first
      ( #(1 2 3 4 5 6 7) from:3 to:7 by:2) last
      ( #(1 2 3 4 5 6 7) from:3 to:7 by:2) size
-    "
+
+     ( #(1 2 3 4 5 6 7) from:7 to:3 by:-2) 
+    "
+
+    "Modified (comment): / 22-02-2017 / 10:52:25 / cg"
+    "Modified (comment): / 08-03-2019 / 13:28:06 / Claus Gittinger"
 !
 
 to:endIndex
@@ -3694,13 +3539,11 @@
      however, physically, no copy is made).
      Warning:
         The slice SHARES the memory for the element-data with the original,
-        this means that any modifications in the original are visible in the slice
-        and vice versa."
-
-    ^ self
-        from:1
-        to:endIndex
-        by:1
+        it is like a readOnly pointer INTO the receiver.
+        This means that any modifications in the original are visible in the slice
+        and vice versa (well, no: because the slice is readOnly)."
+
+    ^ self from:1 to:endIndex by:1
 
     "
      #(1 2 3 4 5 6 7) to:4
@@ -3708,6 +3551,9 @@
      ( #(1 2 3 4 5 6 7) to:4) last
      ( #(1 2 3 4 5 6 7) to:4) size
     "
+
+    "Modified (comment): / 22-02-2017 / 10:49:38 / cg"
+    "Modified (comment): / 08-03-2019 / 13:27:37 / Claus Gittinger"
 !
 
 to:endIndex by:step
@@ -3717,8 +3563,9 @@
      however, physically, no copy is made).
      Warning:
         The slice SHARES the memory for the element-data with the original,
-        this means that any modifications in the original are visible in the slice
-        and vice versa."
+        it is like a readOnly pointer INTO the receiver.
+        This means that any modifications in the original are visible in the slice
+        and vice versa (well, no: because the slice is readOnly)."
 
     ^ self
         from:(step > 0
@@ -3732,7 +3579,11 @@
      ( #(1 2 3 4 5 6 7) to:4 by:2) first
      ( #(1 2 3 4 5 6 7) to:4 by:2) last
      ( #(1 2 3 4 5 6 7) to:4 by:2) size
-    "
+     #(1 2 3 4 5 6 7) to:1 by:-1
+    "
+
+    "Modified (comment): / 22-02-2017 / 10:50:18 / cg"
+    "Modified (comment): / 08-03-2019 / 13:28:32 / Claus Gittinger"
 ! !
 
 !SequenceableCollection methodsFor:'copying'!
@@ -3860,6 +3711,31 @@
     "
 !
 
+copyAfterAll:aCollectionOfElements
+    "Answer a copy of the receiver from after the first occurrence
+     of aCollectionOfElements up to the end. 
+     If no such subsequence exists, answer an empty copy."
+
+    |idx|
+
+    aCollectionOfElements isEmpty ifTrue:[^ self].
+    idx := self indexOfSubCollection:aCollectionOfElements.
+    idx == 0 ifTrue:[idx := self size].
+    ^ self copyFrom:idx + aCollectionOfElements size
+
+    "
+     'hello world' copyAfterAll:'bla'
+     'hello world' copyAfterAll:'hello'
+     '123456123456' copyAfterAll:#($1 $2 $3)
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterAll:#(2 3 4) 
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterAll:#()
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterAll:#(6)
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterAll:#(7)
+    "
+
+    "Created: / 01-11-2018 / 12:23:17 / Claus Gittinger"
+!
+
 copyAfterLast:element
     "return a copy of the receiver from (but excluding) the last occurrence
      of element to the end; uses = for comparison"
@@ -3879,6 +3755,31 @@
     "
 !
 
+copyAfterLastAll:aCollectionOfElements
+    "Answer a copy of the receiver from after the last occurrence
+     of aCollectionOfElements up to the end. 
+     If no such subsequence exists, answer an empty copy."
+
+    |idx|
+
+    aCollectionOfElements isEmpty ifTrue:[^ #()].
+    idx := self lastIndexOfSubCollection:aCollectionOfElements.
+    idx == 0 ifTrue:[idx := self size].
+    ^ self copyFrom:idx + aCollectionOfElements size
+
+    "
+     'hello world' copyAfterLastAll:'bla'
+     'hello world' copyAfterLastAll:'hello'
+     '123456123456' copyAfterLastAll:#($1 $2 $3)
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLastAll:#(2 3 4) 
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLastAll:#()
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLastAll:#(6)
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLastAll:#(7)
+    "
+
+    "Created: / 01-11-2018 / 12:25:58 / Claus Gittinger"
+!
+
 copyButFirst
     "return a new collection consisting of the receiver's elements
      except for the first element.
@@ -3917,6 +3818,25 @@
     "
 !
 
+copyButFirstAndLast
+    "return a new collection consisting of the receiver's elements
+     except for the first and last elements.
+     Raises an error if the receiver's size is less than 2."
+
+    |sz|
+
+    (sz := self size) < 2 ifTrue:[self notEnoughElementsError].
+    ^ self copyFrom:2 to:(sz - 1)
+
+    "
+     #($a $b $c $d $e $f $g) copyButFirstAndLast
+     '1234567890' copyButFirstAndLast
+     '1' copyButFirstAndLast
+     '' copyButFirstAndLast
+     'ab' copyButFirstAndLast
+    "
+!
+
 copyButLast
     "return a new collection consisting of the receiver's elements
      except for the last element.
@@ -4007,6 +3927,29 @@
     "Modified: 20.2.1997 / 14:23:01 / cg"
 !
 
+copyFrom:startIndex through:anElement
+    "return a new collection consisting of receiver's elements from startIndex
+     up to (and including) the next occurence of anElement.
+     Return the remaining elements (up to the end), if anElement is not found. 
+     Return an empty collection, if startIndex is beyond the receiver's size."
+
+    |endIndex|
+
+    endIndex := self indexOf:anElement startingAt:startIndex+1.
+    endIndex == 0 ifTrue:[
+        ^ self copyFrom:startIndex
+    ].        
+    ^ self copyFrom:startIndex to:endIndex
+
+    "
+     #($a $b $c $d $e $f $g) copyFrom:2 through:$f
+     '1234567890' copyFrom:2 through:$8
+     (10 to:19) copyFrom:5 through:18
+    "
+
+    "Created: / 09-11-2018 / 09:37:10 / Claus Gittinger"
+!
+
 copyFrom:startIndex to:stopIndex
     "return a new collection consisting of receiver's elements
      between start and stop.
@@ -4015,6 +3958,13 @@
 
     |newCollection newSize|
 
+    (startIndex < 1) ifTrue:[
+        self subscriptBoundsError:'startindex out of bounds' 
+    ].
+    (stopIndex > self size) ifTrue:[
+        self subscriptBoundsError:'stopindex out of bounds' 
+    ].
+
     newSize := stopIndex - startIndex + 1.
     newSize <= 0 ifTrue:[
         ^ self copyEmpty:0.
@@ -4034,6 +3984,29 @@
     "
 !
 
+copyFrom:startIndex upTo:anElement
+    "return a new collection consisting of receiver's elements from startIndex
+     up to (but excluding) the next occurence of anElement.
+     Return the remaining elements (up to the end), if anElement is not found. 
+     Return an empty collection, if startIndex is beyond the receiver's size."
+
+    |endIndex|
+
+    endIndex := self indexOf:anElement startingAt:startIndex+1.
+    endIndex == 0 ifTrue:[
+        ^ self copyFrom:startIndex
+    ].        
+    ^ self copyFrom:startIndex to:(endIndex - 1)
+
+    "
+     #($a $b $c $d $e $f $g) copyFrom:2 upTo:$f
+     '1234567890' copyFrom:2 upTo:$8
+     (10 to:19) copyFrom:5 upTo:18
+    "
+
+    "Created: / 09-11-2018 / 09:36:11 / Claus Gittinger"
+!
+
 copyLast:count
     "return a new collection consisting of the receiver's last count elements.
      Raises an error if there are not enough elements.
@@ -4169,6 +4142,49 @@
     "Modified (comment): / 16-11-2016 / 21:35:36 / cg"
 !
 
+copyReplaceAllForWhich:checkBlock with:newElement
+    "return a copy of the receiver, where all elements for which checkBlock
+     returns true will are replaced by newElement."
+
+    ^ (self copyFrom:1) replaceAllForWhich:checkBlock with:newElement
+
+    "
+     #(1 2 1 3 4 5 1 2 1 2) copyReplaceAllForWhich:[:e | e > 2] with:99
+     'hello 1234 world' copyReplaceAllForWhich:#isDigit with:$*
+    "
+!
+
+copyReplaceAllSubcollections:subColl with:newColl
+    "return a copy of the receiver, with all sequences of subColl replaced
+     by newColl (i.e. slice in the newColl in place of the subColl)."
+
+    |tmpStream idx idx1|
+
+    tmpStream := self species writeStream.
+    idx := 1.
+    [idx ~~ 0] whileTrue:[
+        idx1 := idx.
+        idx := self indexOfSubCollection:subColl startingAt:idx.
+        idx ~~ 0 ifTrue:[
+            tmpStream nextPutAll:(self copyFrom:idx1 to:idx-1).
+            tmpStream nextPutAll:newColl.
+            idx := idx + subColl size
+        ]
+    ].
+    tmpStream nextPutAll:(self copyFrom:idx1).
+    ^ tmpStream contents
+
+   "
+     #[1 2 3 4 5 6 7 8 9 0 1 2 3 4 5 6 7 8 9 0] copyReplaceAllSubcollections:#[1 2 3] with:#[9 8 7]
+
+     '12345678901234567890' copyReplaceAllSubcollections:'123' with:'OneTwoThree'
+     '12345678901234567890' copyReplaceAllSubcollections:'123' with:'*'
+     '12345678901234567890' copyReplaceAllSubcollections:'234' with:'foo'
+    "
+
+    "Created: / 01-08-2017 / 23:21:11 / cg"
+!
+
 copyReplaceAny:collectionOfOldElements with:newElement
     "return a copy of the receiver, where all elements equal to any in collectionOfOldElements
      have been replaced by newElement."
@@ -4246,6 +4262,67 @@
     "
 !
 
+copyReplacePrefix:oldPrefix with:newPrefix
+    "if the receiver startsWith oldPrefix, return a copy with that suffix replaced by newPrefix.
+     Otherwise return the receiver"
+
+    (self startsWith:oldPrefix) ifTrue:[
+        ^ newPrefix,(self copyFrom:oldPrefix size+1)
+    ].
+    ^ self
+
+    "
+     'helloworld' copyReplacePrefix:'hello' with:'Hello'  
+     'foo class' copyReplacePrefix:'foo' with:'bar'      
+     'ffoo class' copyReplacePrefix:'foo' with:'bar'      
+    "
+
+    "Created: / 12-06-2020 / 14:31:45 / cg"
+!
+
+copyReplaceSubcollection:subColl with:newColl
+    "return a copy of the receiver, with the first occurrence of
+     the subColl sequence replaced by newColl 
+     (i.e. slice in the newColl in place of the first subColl)."
+
+    |idx|
+
+    idx := self indexOfSubCollection:subColl startingAt:1.
+    idx ~~ 0 ifTrue:[
+        ^ (self copyTo:idx-1),newColl,(self copyFrom:idx+subColl size)
+    ].
+    ^ self
+
+   "
+     #[1 2 3 4 5 6 7 8 9 0 1 2 3 4 5 6 7 8 9 0] copyReplaceSubcollection:#[1 2 3] with:#[9 8 7]
+     #[0 0 0 1 2 3 4 5 6 7 8 9 0 1 2 3 4 5 6 7 8 9 0] copyReplaceSubcollection:#[1 2 3] with:#[9 8 7]
+
+     '12345678901234567890' copyReplaceSubcollection:'123' with:'OneTwoThree'
+     '12345678901234567890' copyReplaceSubcollection:'123' with:'*'
+     '12345678901234567890' copyReplaceSubcollection:'234' with:'foo'
+    "
+
+    "Created: / 01-08-2017 / 23:21:42 / cg"
+!
+
+copyReplaceSuffix:oldSuffix with:newSuffix
+    "if the receiver endsWith oldSuffix, return a copy with that suffix replaced by newSuffix.
+     Otherwise return the receiver"
+
+    (self endsWith:oldSuffix) ifTrue:[
+        ^ (self copyButLast:oldSuffix size),newSuffix
+    ].
+    ^ self
+
+    "
+     'helloworld' copyReplaceSuffix:'world' with:'welt'  
+     'foo class' copyReplaceSuffix:' class' with:'Class'     
+     'foo xlass' copyReplaceSuffix:' class' with:'Class'     
+    "
+
+    "Created: / 12-06-2020 / 14:31:55 / cg"
+!
+
 copyReplacing:oldElement withObject:newElement
     "return a copy of the receiver, where all elements equal to oldElement
      have been replaced by newElement.
@@ -4292,7 +4369,7 @@
 copyToMax:stop
     "return a new collection consisting of receiver's elements
      from 1 up to (including) index stop, or up to the receiver's end,
-     whichever is smaller (i.e. like copyTo:, but do not err if receiver is smaller"
+     whichever is smaller (i.e. like copyTo:, but do not err if receiver is smaller)"
 
     ^ self copyFrom:1 to:(self size min:stop)
 
@@ -4300,6 +4377,32 @@
      #($a $b $c $d $e $f $g) copyTo:10  - raises an error
      #($a $b $c $d $e $f $g) copyToMax:10
     "
+
+    "Modified (comment): / 09-06-2018 / 13:07:10 / Claus Gittinger"
+!
+
+copyToMax:stop ifLargerCopyWith:whatToAppendIfLarger
+    "return a new collection consisting of receiver's elements
+     from 1 up to (including) index stop, or up to the receiver's end,
+     whichever is smaller (i.e. like copyTo:, but do not err if receiver is smaller).
+     If the copy is smaller, append the element whatToAppendIfLarger.
+     This is useful to cut off long texts and mark it with '...' at the end
+     as seen in the example below."
+
+    |copySize copy|
+
+    copySize := (self size min:stop).
+    copy := self copyFrom:1 to:copySize.
+    copySize < self size ifTrue:[
+        copy := copy copyWith:whatToAppendIfLarger
+    ].
+    ^ copy
+
+    "
+     (#('one' 'two' 'three' 'four') copyToMax:2 ifLargerCopyWith:'...')
+    "
+
+    "Created: / 09-06-2018 / 13:06:39 / Claus Gittinger"
 !
 
 copyTransliterating:oldElements to:newElements
@@ -4661,6 +4764,16 @@
     "
 !
 
+copyValuesFrom:startIndex 
+    "Return a copy of the receiver that contains values from 
+     position startIndex to the end.
+     For compatibility with OrderedDictionary protocol."
+
+    ^ self copyFrom:startIndex to:self size
+
+    "Created: / 26-02-2019 / 02:24:39 / Claus Gittinger"
+!
+
 copyWith:newElement
     "return a new collection containing the receiver's elements
      and the single new element, newElement.
@@ -4702,7 +4815,7 @@
 
 copyWith:newElement insertedBeforeIndex:index
     "return a new collection with newElement inserted after index.
-     With a 0 index, newElement is prepended;  
+     With a 1 index, newElement is prepended;  
      if index is my size, it is appended.
      The receiver remains unchanged"
 
@@ -4715,6 +4828,8 @@
      #(1 2 3 4 5 6 7 8 9 0 1 2 3 4) copyWith:#a insertedBeforeIndex:15 
      #(1 2 3 4 5 6 7 8 9 0 1 2 3 4) copyWith:#a insertedBeforeIndex:16  --> error
     "
+
+    "Modified (comment): / 16-02-2017 / 14:37:58 / stefan"
 !
 
 copyWithAll:aCollection insertedAfterIndex:index
@@ -4761,14 +4876,14 @@
      This is different from concatentation, which expects two collections
      as argument, but equivalent to copy-and-addFirst."
 
-    |newCollection mySize newSize|
-
-    mySize := self size.
-    newSize := mySize + 1.
+    |newCollection newSize|
+
+    newSize := self size + 1.
     newCollection := self copyEmptyAndGrow:newSize.
-    newCollection replaceFrom:2 to:mySize+1 with:self startingAt:1.
-    newCollection at:1 put:newFirstElement.
-    ^newCollection
+    ^ newCollection 
+        at:1 put:newFirstElement;
+        replaceFrom:2 to:newSize with:self startingAt:1;
+        yourself.
 
     "
      #(1 2 3 4 5) copyWithFirst:$a  
@@ -4776,6 +4891,8 @@
      'abcdefg' copyWithFirst:'123'   -- will fail: string cannot be stored into string
      'abcdefg' copyWithFirst:1       -- will fail: integer cannot be stored into string
     "
+
+    "Modified: / 16-02-2017 / 14:45:03 / stefan"
 !
 
 copyWithout:elementToSkip
@@ -4788,7 +4905,7 @@
      srcIndex  "{ Class: SmallInteger }"
      dstIndex  "{ Class: SmallInteger }"
      skipIndex "{ Class: SmallInteger }"
-     copy l|
+     copy len|
 
     "the code below may look like overkill,
      however, for big collections its better to move data
@@ -4805,6 +4922,63 @@
 
     n timesRepeat:[
         skipIndex := self indexOf:elementToSkip startingAt:srcIndex.
+        len := skipIndex - srcIndex.
+        len ~~ 0 ifTrue:[
+            copy replaceFrom:dstIndex to:(dstIndex + len - 1)
+                        with:self startingAt:srcIndex.
+            dstIndex := dstIndex + len
+        ].
+        srcIndex := skipIndex + 1
+    ].
+    len := sz - srcIndex.
+    copy replaceFrom:dstIndex to:(dstIndex + len)
+                with:self startingAt:srcIndex.
+    ^ copy
+
+    "
+     #($a $b $c $d $e $f $g) copyWithout:$d
+     #($a $b $c $d $e $f $g) copyWithout:$a
+     #($a $b $c $d $e $f $g) copyWithout:$g
+     'abcdefghi' copyWithout:$h
+     'abcdefg' copyWithout:$h
+     'abcdefabcghi' copyWithout:$a
+     'abcdefabcg' copyWithout:$h
+     #($a $b $c $a $a $d $e $a $f $g) copyWithout:$a
+     #($a $b $c $d $e $f $g) copyWithout:$x
+     #(90 80 70 60 50) copyWithout:70
+     #(90 80 70 80 60 45 80 50) copyWithout:80
+    "
+
+    "Modified (format): / 24-10-2017 / 14:45:53 / cg"
+!
+
+copyWithoutAll:elementsToSkip
+    "return a new collection consisting of a copy of the receiver, with
+     ALL elements equal to any in elementsToSkip are left out.
+     No error is reported, if any in elementsToSkip is not in the collection."
+
+    |n         "{ Class: SmallInteger }"
+     sz        "{ Class: SmallInteger }"
+     srcIndex  "{ Class: SmallInteger }"
+     dstIndex  "{ Class: SmallInteger }"
+     skipIndex "{ Class: SmallInteger }"
+     copy l|
+
+    "the code below may look like overkill,
+     however, for big collections its better to move data
+     around in big chunks"
+
+    n := self occurrencesOfAny:elementsToSkip.
+    n == 0 ifTrue:[^ self copyFrom:1].
+
+    sz := self size.
+    copy := self copyEmptyAndGrow:(sz - n).
+
+    srcIndex := 1.
+    dstIndex := 1.
+
+    n timesRepeat:[
+        skipIndex := self indexOfAny:elementsToSkip startingAt:srcIndex.
         l := skipIndex - srcIndex.
         l ~~ 0 ifTrue:[
             copy replaceFrom:dstIndex to:(dstIndex + l - 1)
@@ -4819,15 +4993,9 @@
     ^ copy
 
     "
-     #($a $b $c $d $e $f $g) copyWithout:$d
-     #($a $b $c $d $e $f $g) copyWithout:$a
-     #($a $b $c $d $e $f $g) copyWithout:$g
-     'abcdefghi' copyWithout:$h
-     'abcdefg' copyWithout:$h
-     #($a $b $c $a $a $d $e $a $f $g) copyWithout:$a
-     #($a $b $c $d $e $f $g) copyWithout:$x
-     #(90 80 70 60 50) copyWithout:70
-     #(90 80 70 80 60 45 80 50) copyWithout:80
+     #($a $b $c $d $e $f $g) copyWithoutAll:#($d $b $f)
+     'abcdefghi' copyWithoutAll:'hai'
+     #(90 80 70 80 60 45 80 50) copyWithoutAll:#(80 70 45)
     "
 !
 
@@ -4983,7 +5151,7 @@
      (but excluding) anElement.
      If anElement is not in the receiver, the returned collection
      will be empty.
-     See also #upTo:."
+     See also #upTo:/uptoAll:."
 
     |pos|
 
@@ -5000,6 +5168,31 @@
      '1234.5678' upTo:$.
      '1234.5678' restAfter:$.
     "
+
+    "Modified (comment): / 02-10-2018 / 13:10:07 / Claus Gittinger"
+!
+
+restAfterAll:anElementCollection
+    "return a new collection consisting of the receiver's elements after
+     (but excluding) anElementCollection.
+     If anElementCollection is not in the receiver, the returned collection
+     will be empty.
+     See also #upTo:/upToAll:."
+
+    |pos|
+
+    pos := self indexOfSubCollection:anElementCollection.
+    pos == 0 ifTrue:[^ self copyEmpty].
+
+    ^ self copyFrom:(pos + anElementCollection size)
+
+    "
+     #(1 2 3 4 5 6 7 8 9) upToAll:#(5 6)
+     #(1 2 3 4 5 6 7 8 9) restAfterAll:#(5 6)
+     'hello world' restAfterAll:'hello'
+    "
+
+    "Created: / 02-10-2018 / 13:11:57 / Claus Gittinger"
 !
 
 trimForWhich:aCheckBlock
@@ -5196,6 +5389,44 @@
     "
 !
 
+upToOrSelf:anElement
+    "return a new collection consisting of the receiver's elements upTo
+     (but excluding) anElement.
+     If anElement is not in the receiver, return myself (not a copy!!).
+     See also #restAfter:  , #copyFrom:index.
+
+     This is similar to #upTo: but avoids garbage if anElement is not
+     present in the collection and a copy of the collection is not needed."
+
+    |pos|
+
+    pos := self indexOf:anElement.
+    pos == 0 ifTrue:[^ self].
+
+    ^ self copyFrom:1 to:(pos - 1)
+
+    "
+     #(1 2 3 4 5 6 7 8 9) upToOrSelf:5
+     'hello world' upToOrSelf:Character space
+     #(9 8 7 6 5 4 3 2 1) asSortedCollection upToOrSelf:5
+     '1234.5678' upToOrSelf:$.
+     '1234'      upToOrSelf:$.
+     '.'      upToOrSelf:$.
+
+
+     raises an error:
+
+     (Dictionary new
+        at:#foo put:'foo';
+        at:#bar put:'bar';
+        at:#baz put:'baz';
+        yourself) upToOrSelf:#bar
+
+    "
+
+    "Created: / 09-10-2019 / 10:57:04 / Stefan Vogel"
+!
+
 upToSeparator
     "Return the next elements up to but not including the next separator.
      The next read will return the separator.
@@ -5234,6 +5465,57 @@
     "
 !
 
+withoutPrefix:aStringOrCharacter
+    "if the receiver startsWith aString, return a copy without it.
+     Otherwise return the receiver"
+
+    |startIndex|
+
+    (self startsWith:aStringOrCharacter) ifTrue:[
+        aStringOrCharacter isCharacter ifTrue:[
+            startIndex := 2
+        ] ifFalse:[    
+            startIndex := aStringOrCharacter size+1
+        ].
+        ^ self copyFrom:startIndex
+    ].
+    ^ self
+
+    "
+     'helloworld' withoutPrefix:'hello'   -> 'world'
+     'helloworld' withoutPrefix:'foo'     -> 'helloworld'
+     'helloworld' withoutPrefix:$h        -> 'elloworld'
+     'helloworld' withoutPrefix:#( $h )   -> 'elloworld'
+    "
+
+    "Modified: / 31-07-2018 / 17:05:36 / Claus Gittinger"
+    "Modified (comment): / 24-05-2019 / 09:22:54 / Claus Gittinger"
+    "Modified (comment): / 12-06-2020 / 14:51:20 / cg"
+!
+
+withoutSuffix:aStringOrCharacter
+    "if the receiver endsWith aString, return a copy without it.
+     Otherwise return the receiver"
+
+    (self endsWith:aStringOrCharacter) ifTrue:[
+        aStringOrCharacter isCharacter ifTrue:[
+            ^ self copyButLast:1
+        ] ifFalse:[
+            ^ self copyButLast:aStringOrCharacter size
+        ].
+    ].
+    ^ self
+
+    "
+     'helloworld' withoutSuffix:'world'
+     'helloworld' withoutSuffix:'foo'
+     'helloworldx' withoutSuffix:$x
+    "
+
+    "Created: / 23-10-2017 / 15:01:37 / cg"
+    "Modified: / 31-07-2018 / 17:06:34 / Claus Gittinger"
+!
+
 withoutTrailingForWhich:aCheckBlock
     "return a copy of myself without trailing characters for which aCheckBlock returns true.
      Returns an empty collection, if the receiver consist only of matching chars."
@@ -5280,18 +5562,21 @@
 !
 
 do:aBlock
-    "evaluate the argument, aBlock for every element in the collection."
+    "evaluate the argument, aBlock for every element in the collection in
+     sequence order."
 
     |stop "{ Class:SmallInteger }"|
 
     stop := self size.
     1 to:stop do:[:index |
-	aBlock value:(self at:index).
+        aBlock value:(self at:index).
     ]
 
     "
      #(one two three four five six) do:[:element | Transcript showCR:element]
     "
+
+    "Modified (comment): / 22-06-2017 / 14:51:15 / mawalch"
 !
 
 do:aBlock separatedBy:sepBlock
@@ -5320,27 +5605,27 @@
     "
 !
 
-from:start collect:aBlock
-    "evaluate the argument, aBlock for the elements starting at start
+from:startIndex collect:aBlock
+    "evaluate the argument, aBlock for the elements starting at startIndex
      to the end and return a collection of the results"
 
-    ^ self from:start to:self size collect:aBlock
+    ^ self from:startIndex to:self size collect:aBlock
 
     "
      #(one two three four five six)
-	from:2
-	collect:[:element | element asUppercase]
+        from:2
+        collect:[:element | element asUppercase]
     "
 
     "Created: / 30.1.2000 / 01:02:28 / cg"
 !
 
-from:start conform:aOneArgBlock
-    "return true, if the elements starting at the start-index conform to some condition.
+from:startIndex conform:aOneArgBlock
+    "return true, if the elements starting at the startIndex conform to some condition.
      I.e. return false, if aBlock returns false for any of those elements;
      true otherwise."
 
-    self from:start to:(self size) do:[:element | 
+    self from:startIndex to:(self size) do:[:element | 
         (aOneArgBlock value:element) ifFalse:[^ false]
     ].
     ^ true
@@ -5350,21 +5635,23 @@
 
 from:startIndex do:aBlock
     "evaluate the argument, aBlock for the elements starting with the
-     element at startIndex to the end."
-
-    ^ self from:startIndex to:self size do:aBlock
+     startIndex to the end."
+
+    self from:startIndex to:self size do:aBlock
 
     "
      #(one two three four five six)
-	from:3
-	do:[:element | Transcript showCR:element]
+        from:3
+        do:[:element | Transcript showCR:element]
     "
 !
 
 from:startIndex doWithExit:aBlock
     "evaluate the argument, aBlock for the elements starting with the
-     element at startIndex to the end. Passes an additional exitBlock as second
-     argument, which can be used to exit the loop early."
+     startIndex to the end. Passes an additional exitBlock as second
+     argument, which can be used to exit the loop early.
+     For convenience, return the exit argument if there was an early exit,
+     and nil, if there was not."
 
     ^ self from:startIndex to:self size doWithExit:aBlock
 
@@ -5373,23 +5660,51 @@
         from:3
         doWithExit:[:element :exit | 
             Transcript showCR:element.
-            element = 'four' ifTrue:[ exit value:nil ]
-        ]
+            element = 'four' ifTrue:[ exit value:999 ]
+        ]      
     "
 
     "Created: / 28-07-2013 / 22:37:28 / cg"
 !
 
+from:startIndex doWithIndex:aTwoArgBlock
+    "evaluate the argument, aTwoArgBlock for the elements starting with the
+     startIndex to the end,
+     passing both the element and its index as argument."
+
+    self from:startIndex to:self size doWithIndex:aTwoArgBlock
+
+    "
+     #(one two three four five six)
+        from:3
+        doWithIndex:[:element :idx | Transcript showCR:idx->element]
+    "
+
+    "Created: / 02-05-2019 / 21:01:44 / Claus Gittinger"
+!
+
 from:startIndex keysAndValuesDo:aBlock
     "evaluate the argument, aBlock for the elements and indices starting with the
      element at startIndex to the end."
 
-    ^ self from:startIndex to:self size keysAndValuesDo:aBlock
+    self from:startIndex to:self size keysAndValuesDo:aBlock
 
     "
      #(one two three four five six)
-	from:3
-	keysAndValuesDo:[:element :idx | Transcript showCR:(idx -> element) ]
+        from:3
+        keysAndValuesDo:[:element :idx | Transcript showCR:(idx -> element) ]
+    "
+!
+
+from:startIndex select:aBlock
+    "evaluate the argument, aBlock for the elements starting at startIndex
+     and return a collection of those elements for which the block return true."
+
+    ^ self from:startIndex to:self size select:aBlock
+
+    "
+     #(faba one two three four five six)
+        from:3 select:[:element | element startsWith:'f']
     "
 !
 
@@ -5487,14 +5802,17 @@
 from:index1 to:index2 doWithExit:aBlock
     "evaluate the argument, aBlock for the elements with index index1 to
      index2 in the collection. Pass an additional exitBlock as second argument,
-     which can be used to exit the loop early."
+     which can be used to exit the loop early.
+     For convenience, return the exit argument if there was an early exit,
+     and nil, if there was not."
 
     |exitBlock|
 
-    exitBlock := [:value | ^ value].
-    ^ self from:index1 to:index2 do:[:el |
+    exitBlock := [:exitValue | ^ exitValue firstIfEmpty:nil] asVarArgBlock.
+    self from:index1 to:index2 do:[:el |
         aBlock value:el value:exitBlock
     ].
+    ^ nil
 
     "
      #(one two three four five six)
@@ -5644,7 +5962,8 @@
      and collect the results.
      The block is called with n arguments for group of n consecutive elements in the receiver.
      An error will be reported, if the number of elements in the receiver
-     is not a multiple of n."
+     is not a multiple of n.
+     This is similar to slicesOf:collect:, but here, an N-arg block is expected."
 
     |stop "{ Class:SmallInteger }" newCollection dstIdx argVector rslt|
 
@@ -5694,11 +6013,74 @@
     "Modified: / 27-10-2006 / 10:07:02 / cg"
 !
 
+inGroupsOf:n detect:anNArgBlock thenDo:anotherNArgBlock ifNone:exceptionValue
+    "evaluate the argument, anNArgBlock for every group of n elements in the collection,
+     until the block returns true. Then deliver the to anotherNArgBlock and return
+     that block's result. If none matches, return the valeu from exceptionValue.
+     An error will be reported, if the number of elements in the receiver
+     is not a multiple of n.
+     This is similar to slicesOf:detect:, but here, an N-arg block is expected."
+
+    |stop argVector|
+
+    stop := self size.
+
+    "/ the reason for inlining the cases for 2/3 args is to avoid the temporary object creation, and to    
+    "/ allow for the compiler (jitter) to generate better code for the block-call
+    n == 2 ifTrue:[
+        1 to:stop by:2 do:[:index |
+            |a1 a2|
+
+            a1 := self at:index.
+            a2 := self at:index+1.
+            (anNArgBlock value:a1 value:a2) ifTrue:[
+                ^ anotherNArgBlock value:a1 value:a2
+            ].
+        ].
+        ^ exceptionValue value.
+    ].
+    n == 3 ifTrue:[
+        1 to:stop by:3 do:[:index |
+            |a1 a2 a3|
+
+            a1 := self at:index.
+            a2 := self at:index+1.
+            a3 := self at:index+2.
+            (anNArgBlock value:a1 value:a2 value:a3) ifTrue:[
+                ^ anotherNArgBlock value:a1 value:a2 value:a3
+            ].
+        ].
+        ^ exceptionValue value.
+    ].
+
+    argVector := Array new:n.
+    1 to:stop by:n do:[:index |
+        argVector replaceFrom:1 to:n with:self startingAt:index.
+        (anNArgBlock valueWithArguments:argVector) ifTrue:[
+            ^ anotherNArgBlock valueWithArguments:argVector
+        ].
+    ].
+    ^ exceptionValue value.
+
+    "
+     #(1 one 2 two 3 three 4 four 5 five 6 six)
+         inGroupsOf:2 detect:[:num :sym | num > 3]
+         thenDo:[:num :sym | sym] ifNone:'ouch'   
+
+     #(1 one 2 two 3 three 4 four 5 five 6 six)
+         inGroupsOf:2 detect:[:num :sym | num > 99]
+         thenDo:[:num :sym | sym] ifNone:'ouch'      
+    "
+
+    "Modified: / 27-10-2006 / 10:07:02 / cg"
+!
+
 inGroupsOf:n do:anNArgBlock
     "evaluate the argument, anNArgBlock for every group of n elements in the collection.
      The block is called with n arguments for group of n consecutive elements in the receiver.
      An error will be reported, if the number of elements in the receiver
-     is not a multiple of n."
+     is not a multiple of n.
+     This is similar to slicesOf:do:, but here, an N-arg block is expected."
 
     |stop "{ Class:SmallInteger }" argVector|
 
@@ -5782,22 +6164,6 @@
     "
 !
 
-keysAndValuesConform:aTwoArgBlock
-    "evaluate the argument, aBlock for every element in the collection,
-     passing both index and element as arguments.
-     Return false if any such evaluation returns false, true otherwise."
-
-    self keysAndValuesDo:[:index :el | 
-        (aTwoArgBlock value:index value:el) ifFalse:[^  false].
-    ].
-    ^  true
-
-    "
-     #(10 20 30 40) keysAndValuesConform:[:key :element | element = (key * 10) ]. 
-     #(10 20 30 33 40) keysAndValuesConform:[:key :element | element = (key * 10) ]. 
-    "
-!
-
 keysAndValuesDo:aTwoArgBlock
     "evaluate the argument, aBlock for every element in the collection,
      passing both index and element as arguments."
@@ -5878,9 +6244,9 @@
 
     | mySize "{ Class: SmallInteger }" retval |
 
-    mySize := self size.
-    retval := Array ofSize: mySize - 1.
-    1 to: mySize - 1 do: [:i | 
+    mySize := self size - 1.
+    retval := Array newWithSize: mySize.
+    1 to: mySize do: [:i | 
         retval at: i put: (aTwoArgBlock value: (self at: i) value: (self at: i + 1)) 
     ].
     ^ retval
@@ -5890,10 +6256,12 @@
 
      'hello world how nice' overlappingPairsCollect: [:a :b | a,b]
 
-     (('hello worlld aa bb' overlappingPairsCollect: [:a :b | a,b]) 
+     (('hello world aa bb' overlappingPairsCollect: [:a :b | a,b]) 
         asBag select:[:p | p asSet size = 1])
              valuesSortedByCounts first
     "
+
+    "Modified (comment): / 09-10-2017 / 17:09:01 / stefan"
 !
 
 overlappingPairsDo: aTwoArgBlock 
@@ -5958,7 +6326,7 @@
         but the Squeak-pairsDo: does the same as our pairWiseDo: 
         (sigh: but we were first, so they should have adapted...)"
 
-    ^ self inGroupsOf:2 do:aTwoArgBlock
+    self inGroupsOf:2 do:aTwoArgBlock
 
     "
      #(1 one 2 two 3 three 4 four 5 five 6 six)
@@ -5990,8 +6358,7 @@
 
 select:aBlock
     "evaluate the argument, aBlock for every element in the collection
-     and return a collection of all elements for which the block return
-     true"
+     and return a collection of all elements for which the blocks return true"
 
     |element newColl species needCopy
      sz  "{ Class:SmallInteger }"|
@@ -6029,12 +6396,49 @@
     "
 !
 
+selectIndices:aBlock
+    "evaluate the argument, aBlock for every INDEX in the collection
+     and return a collection of all elements for which the block returns true"
+
+    |element newColl species needCopy
+     sz  "{ Class:SmallInteger }"|
+
+    sz := self size.
+    species := self species.
+    species growIsCheap ifTrue:[
+        newColl := self copyEmpty:sz.
+        needCopy := false
+    ] ifFalse:[
+        sz == 0 ifTrue:[
+            ^ (species new:0) postCopyFrom:self.
+        ].
+        newColl := self speciesForAdding new:sz.
+        needCopy := true
+    ].
+    1 to:sz do:[:index |
+        element := self at:index.
+        (aBlock value:index) ifTrue:[
+            newColl add:element
+        ].
+    ].
+    needCopy ifTrue:[
+        newColl := (species withAll:newColl) postCopyFrom:self
+    ].
+    ^ newColl
+
+    "
+     #(one two three four five six) selectIndices:[:idx | idx odd]   
+     #(1 2 3 4 5 6 7 8 9) selectIndices:#even   
+    "
+!
+
 slicesOf:n collect:aOneArgBlock
     "evaluate the argument, aOneArg for every slice of n elements of the collection,
      and collect the results as instances of targetContainerClass.
      The block is called with n element subcollections for groups of n consecutive elements in the receiver.
      If the number of elements in the receiver is not a multiple of n, the last block evaluation will
-     get a short slice as argument"
+     get a short slice as argument.
+     This is similar to inGroupsOf:collect:, but here, a 1-arg block is expected."
 
     |out|
 
@@ -6055,7 +6459,8 @@
     "evaluate the argument, aOneArg for every slice of n elements of the collection.
      The block is called with n element subcollections for groups of n consecutive elements in the receiver.
      If the number of elements in the receiver is not a multiple of n, the last block evaluation will
-     get a short slice as argument"
+     get a short slice as argument.
+     This is similar to inGroupsOf:do:, but here, a 1-arg block is expected."
 
     |i stop|
 
@@ -6078,6 +6483,194 @@
     "
 !
 
+to:endIndex collect:aBlock
+    "evaluate the argument, aBlock for the elements up 
+     endIndex and return a collection of the results"
+
+    ^ self from:1 to:endIndex collect:aBlock
+
+    "
+     #(one two three four five six)
+        to:3
+        collect:[:element | element asUppercase]
+    "
+!
+
+to:end conform:aOneArgBlock
+    "return true, if the elements up to endIndex conform to some condition.
+     I.e. return false, if aBlock returns false for any of those elements;
+     true otherwise."
+
+    ^ self from:1 to:end conform:aOneArgBlock
+
+
+!
+
+to:endIndex do:aBlock
+    "evaluate the argument, aBlock for the elements starting with the
+     first to the endIndex."
+
+    self from:1 to:endIndex do:aBlock
+
+    "
+     #(one two three four five six)
+        to:3
+        do:[:element | Transcript showCR:element]
+    "
+!
+
+to:endIndex doWithIndex:aTwoArgBlock
+    "evaluate the argument, aTwoArgBlock for the elements starting 
+     with the first to endIndex,
+     passing both the element and its index as argument."
+
+    self from:1 to:endIndex doWithIndex:aTwoArgBlock
+
+    "
+     #(one two three four five six)
+        to:3
+        doWithIndex:[:element :idx | Transcript showCR:idx->element]
+    "
+
+    "Created: / 02-05-2019 / 21:01:44 / Claus Gittinger"
+!
+
+to:endIndex keysAndValuesDo:aBlock
+    "evaluate the argument, aBlock for the elements and indices 
+     starting with the first element to the endIndex."
+
+    self from:1 to:endIndex keysAndValuesDo:aBlock
+
+    "
+     #(one two three four five six)
+        to:3
+        keysAndValuesDo:[:element :idx | Transcript showCR:(idx -> element) ]
+    "
+!
+
+to:endIndex select:aBlock
+    "evaluate the argument, aBlock for the elements up to endIndex
+     and return a collection of those elements for which the block return true."
+
+    ^ self from:1 to:endIndex select:aBlock
+
+    "
+     #(faba one two three four five six)
+        to:3 select:[:element | element startsWith:'f']
+    "
+!
+
+with:aCollection andDefault:defaultElement do:aTwoArgBlock
+    "evaluate the argument, aBlock for successive elements from
+     each the receiver and the argument, aCollection.
+     If the receiver has more elements than the argument, use defaultElement 
+     for remaining evaluations.
+     The third argument, aTwoArgBlock must be a two-argument block.
+     This method fails if neither the receiver nor aCollection is
+     a sequenceable collection (i.e. implements numeric key access)"
+
+    |index  "{ Class: SmallInteger }"
+     sz  "{ Class: SmallInteger }"|
+
+    index := 1.
+    sz := self size.
+
+    "aCollection may be non-sequenceable, but we are"
+    aCollection do:[:eachElement |
+        index >= sz ifTrue:[
+           ^ self.
+        ].
+        aTwoArgBlock value:(self at:index) value:eachElement.
+        index := index + 1.
+    ].
+
+    "I have more elements than aCollection"
+    index to:sz do:[:i|
+        aTwoArgBlock value:(self at:index) value:defaultElement.
+    ].
+        
+
+    "
+     #(1 2 3) with:#(one two) andDefault:99 do:[:num :sym |
+        Transcript showCR:(num->sym)
+     ]
+
+     #() with:#(one two) andDefault:99 do:[:num :sym |
+        Transcript showCR:(num->sym)
+     ]
+
+     'this example does not really make sense'
+     #(1 2 3) with:#(one two) asSet andDefault:99 do:[:num :sym |
+        Transcript showCR:(num->sym)
+     ]
+    "
+
+    "Created: / 28-04-2017 / 12:13:34 / stefan"
+    "Modified: / 28-04-2017 / 14:56:40 / stefan"
+!
+
+with:collection2 collect:aTwoArgBlock
+    "evaluate the argument, aBlock for successive elements from
+     each the receiver and the collection argument,
+     and collect the results.
+     The last argument, aBlock must be a two-argument block.
+     The collection arguments must implement access via a numeric key 
+     and the sizes must be the same."
+
+    ^ self with:collection2 collect:aTwoArgBlock as:self speciesForAdding
+
+    "
+     #(one two three four five six)
+        with:(100 to:600 by:100)
+        collect:[:el1 :el2 | 
+            el1 printString , el2 printString
+        ]
+    "
+
+    "Modified (Format): / 30-06-2011 / 17:39:59 / cg"
+
+    "Created: / 20-12-2018 / 11:12:04 / Claus Gittinger"
+    "Modified: / 22-12-2018 / 09:57:38 / Claus Gittinger"
+!
+
+with:collection2 collect:aTwoArgBlock as:classOfResult
+    "evaluate the argument, aBlock for successive elements from
+     each the receiver and the collection argument,
+     and collect the results.
+     The last argument, aBlock must be a two-argument block.
+     The collection arguments must implement access via a numeric key 
+     and the sizes must be the same."
+
+    |stop  "{ Class: SmallInteger }" 
+     newCollection|
+
+    stop := self size.
+    (collection2 size == stop)  ifFalse:[
+        NotEnoughElementsSignal raiseRequestErrorString:'collections must be of the same size'.
+    ].
+    
+    newCollection := classOfResult new.
+    1 to:stop do:[:index |
+        newCollection add:(
+            aTwoArgBlock 
+                value:(self at:index) 
+                value:(collection2 at:index))
+    ].
+    ^ newCollection
+    
+    "
+     #(one two three four five six)
+        with:(100 to:600 by:100)
+        collect:[:el1 :el2 | 
+            el1 printString , el2 printString
+        ]
+    "
+
+    "Modified (Format): / 30-06-2011 / 17:39:59 / cg"
+
+    "Created: / 22-12-2018 / 09:56:59 / Claus Gittinger"
+!
+
 with:aSequenceableCollection do:aTwoArgBlock
     "evaluate the argument, aBlock for successive elements from
      each the receiver and the argument, aSequenceableCollection.
@@ -6136,6 +6729,96 @@
     "Modified (comment): / 08-01-2012 / 17:18:59 / cg"
 !
 
+with:collection2 select:aTwoArgBlock
+    "evaluate the argument, aBlock for successive elements from
+     each the receiver and the collection argument,
+     and select values from the receiver, where aTwoArgBlock returns true.
+     The collection arguments must implement access via a numeric key 
+     and the sizes must be the same."
+
+    |newCollection|
+    
+    newCollection := self speciesForAdding new.
+    self with:collection2 
+        do:[:el :el2 | 
+            (aTwoArgBlock value:el value:el2) ifTrue:[
+                newCollection add:el.
+            ]
+        ].
+    ^ newCollection
+    
+    "to fetch all elements at even indices:
+    
+     #(one two three four five six seven eight) with:(1 to:8) select:[:el :idx | idx even]
+    "
+
+    "Created: / 19-07-2019 / 11:13:58 / Claus Gittinger"
+!
+
+with:collection2 with:collection3 collect:aThreeArgBlock
+    "evaluate the argument, aBlock for successive elements from
+     each the receiver and the collection arguments
+     and collect the results.
+     The last argument, aBlock must be a three-argument block.
+     The collection arguments must implement access via a numeric key 
+     and the sizes must be the same."
+
+    ^ self with:collection2 with:collection3 collect:aThreeArgBlock as:self speciesForAdding
+
+    "
+     #(one two three four five six)
+        with:(1 to:6)
+        with:(100 to:600 by:100)
+        collect:[:el1 :el2 :el3 | 
+            el1 printString , el2 printString , el3 printString
+        ]
+    "
+
+    "Modified (Format): / 30-06-2011 / 17:39:59 / cg"
+
+    "Created: / 20-12-2018 / 11:11:07 / Claus Gittinger"
+    "Modified: / 22-12-2018 / 09:58:50 / Claus Gittinger"
+!
+
+with:collection2 with:collection3 collect:aThreeArgBlock as:classOfResult
+    "evaluate the argument, aBlock for successive elements from
+     each the receiver and the collection arguments
+     and collect the results.
+     The last argument, aBlock must be a three-argument block.
+     The collection arguments must implement access via a numeric key 
+     and the sizes must be the same."
+
+    |stop  "{ Class: SmallInteger }" 
+     newCollection|
+
+    stop := self size.
+    (collection2 size == stop and:[collection3 size == stop])  ifFalse:[
+        NotEnoughElementsSignal raiseRequestErrorString:'collections must be of the same size'.
+    ].
+
+    newCollection := classOfResult new.
+    1 to:stop do:[:index |
+        newCollection add:(aThreeArgBlock 
+            value:(self at:index) 
+            value:(collection2 at:index)
+            value:(collection3 at:index)).
+    ].
+    ^ newCollection
+
+    "
+     #(one two three four five six)
+        with:(1 to:6)
+        with:(100 to:600 by:100)
+        collect:[:el1 :el2 :el3 | 
+            el1 printString , el2 printString , el3 printString
+        ]
+    "
+
+    "Modified (Format): / 30-06-2011 / 17:39:59 / cg"
+
+    "Created: / 22-12-2018 / 09:57:50 / Claus Gittinger"
+!
+
 with:collection2 with:collection3 do:aThreeArgBlock
     "evaluate the argument, aBlock for successive elements from
      each the receiver and the collection arguments.
@@ -6171,6 +6854,7 @@
 
 atAllPut:anObject
     "replace all elements of the collection by the argument, anObject.
+     Return the receiver.
      Notice: This operation modifies the receiver, NOT a copy;
      therefore the change may affect all others referencing the receiver."
 
@@ -6187,7 +6871,32 @@
      (String new:10) atAllPut:$a
     "
 
-    "Modified: / 20.5.1998 / 15:14:11 / cg"
+    "Modified: / 20-05-1998 / 15:14:11 / cg"
+    "Modified (comment): / 26-03-2019 / 11:53:31 / Claus Gittinger"
+!
+
+clearContents
+    "to be used with cryptographic keys, to wipe their contents after use"
+
+    self atAllPut:0
+!
+
+from:startIndex count:numberOfElements put:newElement
+    "replace numberOfElements elements from startIndex of the collection
+     by the argument, newElement.
+     Notice: This operation modifies the receiver, NOT a copy;
+     therefore the change may affect all others referencing the receiver."
+
+    ^ self
+        from:startIndex
+        to:(startIndex + numberOfElements - 1)
+        put:newElement
+
+    "
+     #($a $b $c $d $e $f $g) copy from:2 count:3 put:nil
+     '1234567890' copy from:2 count:5 put:$*
+     '1234567890' copy from:2 count:20 put:$* -> error
+    "
 !
 
 from:index1 to:index2 put:anObject
@@ -6303,17 +7012,17 @@
 
     start := startIndex.
     stop := stopIndex.
-    startIndex to:stopIndex do:[:index |
-	(self at:index) = oldObject ifTrue:[
-	    self at:index put:newObject
-	]
+    start to:stop do:[:index |
+        (self at:index) = oldObject ifTrue:[
+            self at:index put:newObject
+        ]
     ]
 
     "
      args:    oldObject  : <object>
-	      newObject  : <object>
-	      startIndex : <integer>
-	      stopIndex  : <integer>
+              newObject  : <object>
+              startIndex : <integer>
+              stopIndex  : <integer>
 
      returns: self
     "
@@ -6324,7 +7033,8 @@
      #(1 2 3 4 1 2 3 4) replaceAll:1 with:'one' from:1 to:4
     "
 
-    "Modified: / 20.5.1998 / 15:23:10 / cg"
+    "Modified: / 20-05-1998 / 15:23:10 / cg"
+    "Modified: / 22-02-2019 / 10:08:08 / Stefan Vogel"
 !
 
 replaceAllForWhich:aConditionBlock with:newObject
@@ -6335,15 +7045,28 @@
      therefore the change may affect all others referencing the receiver."
 
     self
-	replaceAllForWhich:aConditionBlock with:newObject
-	from:1 to:(self size)
+        replaceAllForWhich:aConditionBlock with:newObject
+        from:1 to:(self size)
 
     "
      args:    aConditionBlock  : <block>
-	      newObject        : <object>
+              newObject        : <object>
 
      returns: self
     "
+    
+    "
+     ('bla',Character tab,'bla',Character cr,'bla') 
+        replaceAllForWhich:[ch: ch isSeparator]
+        with:(Character space)
+
+     ('bla',Character tab,'bla',Character cr,'bla') 
+        replaceAllForWhich:#isSeparator
+        with:(Character space)
+
+    "
+
+    "Modified (format): / 18-07-2017 / 13:28:45 / cg"
 !
 
 replaceAllForWhich:aConditionBlock with:newObject from:startIndex to:stopIndex
@@ -6358,20 +7081,22 @@
 
     start := startIndex.
     stop := stopIndex.
-    startIndex to:stopIndex do:[:index |
-	(aConditionBlock value:(self at:index)) ifTrue:[
-	    self at:index put:newObject
-	]
+    start to:stop do:[:index |
+        (aConditionBlock value:(self at:index)) ifTrue:[
+            self at:index put:newObject
+        ]
     ]
 
     "
      args:    aConditionBlock  : <block>
-	      newObject        : <object>
-	      startIndex       : <integer>
-	      stopIndex        : <integer>
+              newObject        : <object>
+              startIndex       : <integer>
+              stopIndex        : <integer>
 
      returns: self
     "
+
+    "Modified: / 22-02-2019 / 11:22:27 / Stefan Vogel"
 !
 
 replaceAllIdentical:oldObject with:newObject
@@ -6414,17 +7139,17 @@
 
     start := startIndex.
     stop := stopIndex.
-    startIndex to:stopIndex do:[:index |
-	(self at:index) == oldObject ifTrue:[
-	    self at:index put:newObject
-	]
+    start to:stop do:[:index |
+        (self at:index) == oldObject ifTrue:[
+            self at:index put:newObject
+        ]
     ]
 
     "
      args:    oldObject  : <object>
-	      newObject  : <object>
-	      startIndex : <integer>
-	      stopIndex  : <integer>
+              newObject  : <object>
+              startIndex : <integer>
+              stopIndex  : <integer>
 
      returns: self
     "
@@ -6434,6 +7159,8 @@
      #(1 2 3 4 1.0 2.0 3.0 4.0) replaceAll:1 with:'one' from:1 to:8
      #(1 2 3 4 1.0 2.0 3.0 4.0) replaceAllIdentical:1 with:'one' from:1 to:8
     "
+
+    "Modified: / 22-02-2019 / 11:22:48 / Stefan Vogel"
 !
 
 replaceAny:aCollection by:newObject
@@ -6520,17 +7247,17 @@
 
     start := startIndex.
     stop := stopIndex.
-    startIndex to:stopIndex do:[:index |
-	(aCollection includes:(self at:index)) ifTrue:[
-	    self at:index put:newObject
-	]
+    start to:stop do:[:index |
+        (aCollection includes:(self at:index)) ifTrue:[
+            self at:index put:newObject
+        ]
     ]
 
     "
      args:    aCollection    : <colleciton of <object> >
-	      newObject      : <object>
-	      startIndex     : <integer>
-	      stopIndex      : <integer>
+              newObject      : <object>
+              startIndex     : <integer>
+              stopIndex      : <integer>
 
      returns: self
     "
@@ -6540,7 +7267,8 @@
      #('foo' 'bar' 'foo' 'baz' foo 1 2 3) replaceAny:#(foo 1) with:'*'
     "
 
-    "Modified: / 20.5.1998 / 15:22:43 / cg"
+    "Modified: / 20-05-1998 / 15:22:43 / cg"
+    "Modified: / 22-02-2019 / 11:23:00 / Stefan Vogel"
 !
 
 replaceFrom:startIndex count:numberOfElements with:replacementCollection
@@ -6628,7 +7356,7 @@
      end      "{ Class: SmallInteger }" |
 
     replacementCollection == self ifTrue:[
-        repStartIndex == startIndex ifTrue:[ "noting to copy" ^ self ].
+        repStartIndex == startIndex ifTrue:[ "nothing to copy" ^ self ].
 
         "beware the overlapping copy"
         (repStartIndex < startIndex) ifTrue:[
@@ -6678,6 +7406,7 @@
     "
 
     "Modified: / 08-05-2012 / 13:23:51 / cg"
+    "Modified (format): / 29-05-2017 / 16:12:44 / mawalch"
 !
 
 replaceFrom:startIndex with:replacementCollection
@@ -7138,7 +7867,7 @@
 printStringWithSeparator:aSeparatorStringOrCharacter
     |s|
 
-    s := CharacterWriteStream on:''.
+    s := CharacterWriteStream new.
     self printOn:s withSeparator:aSeparatorStringOrCharacter.
     ^ s contents.
 
@@ -7149,10 +7878,10 @@
 
 !SequenceableCollection methodsFor:'private-sorting helpers'!
 
-mergeFirst:first middle:middle last:last into:dst by:aBlock 
+mergeFirst:first middle:middle last:last into:dst by:aBlock
     "Private!!
      Merge the sorted ranges [first..middle] and [middle+1..last] of the receiver into the range [first..last] of dst."
-    
+
     |i1 i2 val1 val2 out|
 
     i1 := first.
@@ -7164,7 +7893,7 @@
         val2 := self at:i2.
         "select 'lower' half of the elements based on comparator"
         [(i1 <= middle) and:[i2 <= last]] whileTrue:[
-            "this is stable if #< or #> ist used for comparison (and not #<= or #>=)"
+            "this is stable if #< or #> is used for comparison (and not #<= or #>=)"
             (aBlock value:val2 value:val1) ifTrue:[
                 dst at:out put:val2.
                 i2 := i2 + 1.
@@ -7182,18 +7911,20 @@
 
     "copy the remaining elements"
     i1 <= middle ifTrue:[
-        dst 
+        dst
             replaceFrom:out
             to:last
             with:self
             startingAt:i1
     ] ifFalse:[
-        dst 
+        dst
             replaceFrom:out
             to:last
             with:self
             startingAt:i2
     ].
+
+    "Modified (format): / 21-02-2017 / 14:33:35 / mawalch"
 !
 
 mergeSortFrom: first to: last by: aBlock
@@ -7859,9 +8590,15 @@
 !
 
 isSequenceable
-    "return true, if the receiver is some kind of sequenceableCollection"
+    "return true, if the receiver is sequenceable,
+     i.e. if its elements are accessible via the #at: and #at:put: messages
+     by an integer index, and support the do:-protocol."
 
     ^ true
+
+    "Modified (comment): / 03-03-2019 / 00:09:21 / Claus Gittinger"
+    "Modified (comment): / 15-04-2019 / 19:24:14 / Stefan Vogel"
+    "Modified (comment): / 26-05-2020 / 17:11:18 / cg"
 !
 
 isSorted
@@ -7906,13 +8643,13 @@
 !
 
 keys
-    "return a collection with all keys in the Smalltalk dictionary"
+    "return a collection with all keys of the receiver"
 
     |sz|
 
     sz := self size.
     sz == 0 ifTrue:[
-	^ #()
+        ^ #()
     ].
     ^ 1 to:sz
 !
@@ -8124,7 +8861,26 @@
 !
 
 findFirst:aBlock startingAt:startIndex
-    "find the first element, for which evaluation of the argument, aBlock returns true.
+    "find the index of the first element, for which evaluation of the argument, aBlock returns true.
+     Start the search at startIndex.
+     Return its index or 0 if none detected.
+     This is much like #detect:startingAt:, however, here an INDEX is returned,
+     whereas #detect: returns the element."
+
+    ^ self findFirst:aBlock startingAt:startIndex ifNone:0
+
+    "
+     #(1 4 3 4 3 6) findFirst:[:x | (x > 3)] startingAt:4    
+     'one.two.three' findFirst:[:c | (c == $.)] startingAt:5 
+     'one.two.three' findFirst:[:c | (c == $.)] startingAt:9 
+    "
+
+    "Modified: / 21-10-1998 / 18:48:22 / cg"
+    "Modified (comment): / 28-05-2018 / 13:10:43 / Claus Gittinger"
+!
+
+findFirst:aBlock startingAt:startIndex ifNone:exceptionalValue
+    "find the index of the first element, for which evaluation of the argument, aBlock returns true.
      Start the search at startIndex.
      Return its index or 0 if none detected.
      This is much like #detect:startingAt:, however, here an INDEX is returned,
@@ -8138,14 +8894,17 @@
     start to:stop do:[:index |
         (aBlock value:(self at:index)) ifTrue:[^ index].
     ].
-    ^ 0
+    ^ exceptionalValue value
 
     "
      #(1 4 3 4 3 6) findFirst:[:x | (x > 3)] startingAt:4
      'one.two.three' findFirst:[:c | (c == $.)] startingAt:5
-    "
-
-    "Modified: / 21.10.1998 / 18:48:22 / cg"
+     'one.two.three' findFirst:[:c | (c == $.)] startingAt:10
+     'one.two.three' findFirst:[:c | (c == $.)] startingAt:10 ifNone:nil
+    "
+
+    "Modified: / 21-10-1998 / 18:48:22 / cg"
+    "Modified (comment): / 28-05-2018 / 13:10:33 / Claus Gittinger"
 !
 
 findLast:aBlock ifNone:exceptionalValue
@@ -8338,7 +9097,10 @@
      #(1 2 1 2 1 2 3) indexOfSubCollection:#(1 2)   startingAt:2
      #(1 2 1 2 1 2 3) indexOfSubCollection:#(1 2)   startingAt:3
      #(1 2 1 2 1 2 3) indexOfSubCollection:#(1 2)   startingAt:4
-    "
+     #(0 1 2 3 15921909 15921909 15921909 15921909 15921909 15921909 15921909 15921909 15921909 15921909 15921909 15921909) indexOfSubCollection:#(15921909 15921909 15921909 15921909 15921909 15921909)
+    "
+
+    "Modified (comment): / 03-02-2017 / 15:57:26 / cg"
 !
 
 lastIndexOfSubCollection:aCollection
@@ -8666,6 +9428,43 @@
     "Modified: / 20.5.1998 / 14:58:05 / cg"
 !
 
+indexOf:anElement startingAt:start step:step
+    "search the collection for anElement, starting the search at index start;
+     if found, return the index otherwise return 0.
+     Only look at every step element.
+     The comparison is done using =
+     (i.e. equality test - not identity test)."
+
+    |startIndex "{ Class: SmallInteger }"
+     stepCount  "{ Class: SmallInteger }" 
+     stop       "{ Class: SmallInteger }" |
+
+    startIndex := start.
+    stop := self size.
+    stepCount := step.
+    startIndex to:stop by:stepCount do:[:index |
+        anElement = (self at:index) ifTrue:[^ index].
+    ].
+    ^ 0
+
+    "
+     args:    anElement : <object>
+              start     : <integer>
+              step     : <integer>
+
+     returns: elementIndex - if found
+              0            - if not found
+    "
+
+    "
+     #(10 20 30 40 10 20 30 40) indexOf:40   startingAt:5
+     #(10 20 30 40 10 20 30 40) indexOf:40.0 startingAt:5
+    "
+
+    "Created: / 18-09-2018 / 14:06:32 / Stefan Vogel"
+    "Modified (comment): / 22-10-2019 / 19:57:19 / Stefan Vogel"
+!
+
 indexOfAny:aCollection
     "search the collection for an element in aCollection.
      if found, return the index otherwise return 0.
@@ -8768,6 +9567,31 @@
 
 !
 
+indicesOf:anElement
+    "search the collection for all occurrences of anElement;
+     return a collection of indices, or an empty collection if not found.
+     The comparison is done using =
+     (i.e. equality test - not identity test)."
+
+     |indices startIndex index|
+
+     indices := OrderedCollection new.
+     startIndex := 1.
+     [ (index := self indexOf:anElement startingAt:startIndex) ~~ 0 ] whileTrue:[
+        indices add:index.
+        startIndex := index + 1.
+     ].
+     ^ indices
+
+"<<END
+     #(10 20 30 40 10 20 30 50 60 10 20 30 70) indicesOf:20 
+     'abc "123" def "555"' indicesOf:$"
+     'abc: bla bla bla: "555"' indicesOf:$:
+END"
+
+    "Modified: / 20.5.1998 / 14:59:55 / cg"
+!
+
 lastIndexOf:anElement
     "search the collection backwards for anElement;
      if found, return the index otherwise return 0.
@@ -8915,7 +9739,7 @@
 
     startIndex := start.
     stopIndex :=  stop.
-    startIndex to:stop do:[:index |
+    startIndex to:stopIndex do:[:index |
         anElement = (self at:index) ifTrue:[^ index].
     ].
     ^ 0
@@ -8937,6 +9761,7 @@
 
     "Modified: / 23-09-2011 / 14:03:05 / cg"
     "Modified (comment): / 19-11-2016 / 13:04:56 / cg"
+    "Modified: / 22-02-2019 / 10:07:17 / Stefan Vogel"
 !
 
 nextIndexOf:anElement from:start to:stop ifAbsent:exceptionBlock
@@ -9477,6 +10302,22 @@
     self addFirst:anElement.
 !
 
+removeAndAddFirst:anElement limitSizeTo:maxSize
+    "if the anElement is in the receiver collection, remove it (compare by equality);
+     then add it to the beginning.
+     Effectively moving the element to the beginning if it is already present,
+     or adding it to the beginning if not already there.
+     If the receiver's size grows over maxSize, then the last element is removed,
+     to implement a history behavior (keep the last maxSize used elements)"
+
+    self removeAndAddFirst:anElement.
+    self size > maxSize ifTrue:[
+        self removeFromIndex:(maxSize + 1).
+    ].
+
+    "Created: / 19-05-2020 / 12:27:37 / cg"
+!
+
 removeAndAddLast:anElement
     "if the anElement is in the receiver collection, remove it (compare by equality);
      then add it to the end.
@@ -9492,12 +10333,26 @@
      WARNING: this is a destructive operation, which modifies the receiver.
               Please use reversed (with a d) for a functional version."
 
+    self reverseFrom:1 to:self size
+
+    "
+     #(4 5 6 7 7) copy reverse
+     #(1 4 7 10 2 5) asOrderedCollection reverse
+    "
+
+    "Modified (comment): / 01-05-2017 / 12:46:23 / cg"
+!
+
+reverseFrom:startIndex to:endIndex
+    "destructively reverse the order of some elements inplace.
+     WARNING: this is a destructive operation, which modifies the receiver."
+
     |lowIndex "{ Class: SmallInteger }"
      hiIndex  "{ Class: SmallInteger }"
      t1 t2|
 
-    hiIndex := self size.
-    lowIndex := 1.
+    hiIndex := endIndex.
+    lowIndex := startIndex.
     [lowIndex < hiIndex] whileTrue:[
         t1 := self at:lowIndex.  t2 := self at:hiIndex.
         self at:lowIndex put:t2.  self at:hiIndex put:t1.
@@ -9507,9 +10362,10 @@
     ]
 
     "
-     #(4 5 6 7 7) reverse
-     #(1 4 7 10 2 5) asOrderedCollection reverse
-    "
+     #(1 2 3 4 5) copy reverseFrom:2 to:4
+    "
+
+    "Created: / 01-05-2017 / 12:45:26 / cg"
 !
 
 reversed
@@ -9623,6 +10479,26 @@
     "
 !
 
+sortByValue
+    "Sort my contents inplace based on sending #value to my
+     elements. 
+     Sorting by a #value selector is so common, that its worth a separate utility"
+
+    ^ self sort:[:a :b | a value < b value ]
+
+    "
+     replace all uses of sort as in:
+        ... sort:[:a :b | a value < b value]
+     by:
+        ... sortByValue
+
+     find these by searching for code matching (code-search in the browser's method list):
+        `@e sort:[:a :b | a value < b value ]
+    "
+
+    "Created: / 13-07-2017 / 20:38:42 / cg"
+!
+
 sortWith:aCollection
     "sort the receiver collection inplace, using '<' to compare elements.
      Also, the elements of aCollection are reordered with it.
@@ -9968,7 +10844,7 @@
 
 insertionSort:sortBlock from:inBegin to:inEnd
     "binary insertion sort.
-     The implementation uses the insertionSort algorithm, 
+     The implementation uses the insertionSort algorithm,
      which is slow for large collections O(n*n), but good for small or
      almost sorted collections O(N)."
 
@@ -9982,7 +10858,7 @@
     begin to:end do:[:idx|
         temp := self at:idx.
         prevIdx := idx-1.
-        "this is stable if #< or #> ist used for comparison (and not #<= or #>=)"
+        "this is stable if #< or #> is used for comparison (and not #<= or #>=)"
         [prevIdx >= inBegin and:[sortBlock value:temp value:(self at:prevIdx)]] whileTrue:[
             self at:prevIdx+1 put:(self at:prevIdx).
             prevIdx := prevIdx - 1.
@@ -10006,6 +10882,8 @@
      data reverse.
      Transcript show:'insert reverse '; showCR:(Time millisecondsToRun:[data insertionSort]).
     "
+
+    "Modified (comment): / 21-02-2017 / 14:33:09 / mawalch"
 !
 
 mergeSort
@@ -10114,7 +10992,7 @@
     startIndex = stopIndex ifTrue:[
         ^ self
     ].
-    (startIndex >= 1 and:[ startIndex < stopIndex ]) ifFalse:[
+    (startIndex > 0 and:[ startIndex < stopIndex ]) ifFalse:[
         self error:'bad start index'
     ].
     stopIndex > mySize ifTrue:[
@@ -10188,7 +11066,7 @@
 
     stop := self size.
     (stop > 1) ifTrue:[
-        sortBlock numArgs == 3 ifTrue:[
+        sortBlock argumentCount == 3 ifTrue:[
             "/ TODO: pass a collating policy to aBlock
             self quickSortFrom:1 to:stop sortBlock:sortBlock policy:(StringCollationPolicy new)
         ] ifFalse:[
@@ -10402,20 +11280,772 @@
     "
 ! !
 
+!SequenceableCollection methodsFor:'splitting & joining'!
+
+asCollectionOfSubCollectionsOfSize:pieceSize
+    "slice into pieces; return a collection containing pieces of size pieceSize from the receiver.
+     The last piece may be smaller, if the receiver's size is not a multiple of pieceSize."
+
+    |pieces
+     start  "{ Class:SmallInteger }"
+     stop   "{ Class:SmallInteger }"
+     mySize "{ Class:SmallInteger }"|
+
+    pieces := self speciesForSubcollection new.
+    start := 1. stop := start + pieceSize - 1.
+    mySize := self size.
+    [stop <= mySize] whileTrue:[
+        pieces add:(self copyFrom:start to:stop).
+        start := start + pieceSize.
+        stop := stop + pieceSize.
+    ].
+    (start <= mySize) ifTrue:[
+        pieces add:(self copyFrom:start to:mySize).
+    ].
+    ^ pieces
+
+    "
+     '123123123123123123' asCollectionOfSubCollectionsOfSize:3 
+     '12312312312312312312' asCollectionOfSubCollectionsOfSize:3 
+    "
+
+    "Modified: / 24-01-2017 / 18:55:07 / stefan"
+!
+
+asCollectionOfSubCollectionsSeparatedBy:anElement do:aBlock
+    "evaluate aBlock for each subcollection generated by separating elements
+     of the receiver by anElement.
+     If anElement occurs multiple times in a row,
+     the block will be invoked with empty collections as argument.
+     This algorithm uses equality-compare to detect the element."
+
+    |subCollection
+     endIndex      "{ Class:SmallInteger }"
+     startIndex    "{ Class:SmallInteger }"
+     stopIndex     "{ Class:SmallInteger }" |
+
+    startIndex := 0.
+    endIndex := self size.
+
+    [startIndex <= endIndex] whileTrue:[
+        stopIndex := self indexOf:anElement startingAt:startIndex+1.
+        stopIndex == 0 ifTrue:[
+            stopIndex := self size
+        ] ifFalse: [
+            stopIndex := stopIndex - 1.
+        ].
+
+        (stopIndex < startIndex) ifTrue: [
+            subCollection := self species new:0
+        ] ifFalse: [
+            subCollection := self copyFrom:startIndex+1 to:stopIndex
+        ].
+        aBlock value:subCollection.
+        startIndex := stopIndex + 1
+    ].
+
+    "
+     '' 
+        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
+
+     '1 one' 
+        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
+
+     '1 one:2 two:3 three:4 four:5 five' 
+        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
+
+     'a::b' 
+        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
+
+     ':' 
+        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
+
+     ':a' 
+        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
+
+     'a:' 
+        asCollectionOfSubCollectionsSeparatedBy:$: do:[:each | Transcript showCR:each storeString]
+    "
+!
+
+asCollectionOfSubCollectionsSeparatedByAll:aSeparatorCollection do:aBlock
+    "evaluate aBlock for each subcollection generated by separating elements
+     of the receiver by aSeparatorCollection. 
+     If aSeparatorCollection occurs multiple times in a row,
+     the result will contain empty strings.
+     Uses equality-compare when searching for aSeparatorCollection."
+
+    |items done myClass
+     startIndex    "{ Class:SmallInteger }"
+     stopIndex     "{ Class:SmallInteger }" |
+
+    items := self speciesForSubcollection new.
+    myClass := self species.
+
+    startIndex := 1.
+    done := false.
+    [done] whileFalse:[
+        |subCollection|
+
+        stopIndex := self indexOfSubCollection:aSeparatorCollection startingAt:startIndex.
+        stopIndex == 0 ifTrue:[
+            stopIndex := self size.
+            done := true.
+        ] ifFalse: [
+            stopIndex := stopIndex - 1.
+        ].
+
+        (stopIndex < startIndex) ifTrue: [
+            subCollection := myClass new:0.
+        ] ifFalse: [
+            subCollection := self copyFrom:startIndex to:stopIndex.
+        ].
+        aBlock value:subCollection.
+        startIndex := stopIndex + (aSeparatorCollection size) + 1.
+    ].
+    ^ items
+
+    "
+     '1::2::3::4::5::' asCollectionOfSubCollectionsSeparatedByAll:'::'
+     #(1 2 3 1 2 3 4 3 1 1 2 3 1 4 5) asCollectionOfSubCollectionsSeparatedByAll:#(3 1)
+     'hello+#world+#here' asCollectionOfSubCollectionsSeparatedByAll:'+#'
+    "
+
+    "Created: / 20-09-2017 / 18:58:11 / stefan"
+!
+
+asCollectionOfSubCollectionsSeparatedByAny:aCollectionOfSeparators
+    "return a collection containing the subCollection
+     (separated by any from aCollectionOfSeparators) of the receiver.
+     This allows breaking up strings using a number of elements as separator.
+     Uses equality-compare when searching for separators."
+
+    ^ self asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:el | aCollectionOfSeparators includes:el]
+
+    "
+     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAny:#($:)
+     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAny:':'
+     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAny:(Array with:$: with:Character space)
+     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAny:': '
+     'h1e2l3l4o' asCollectionOfSubCollectionsSeparatedByAny:($1 to: $9)
+     #(1 9 2 8 3 7 4 6 5 5) asCollectionOfSubCollectionsSeparatedByAny:#(1 2 3)
+    "
+!
+
+asCollectionOfSubCollectionsSeparatedByAnyChange:aTwoArgBlock 
+    "Answer an ordered collection of ordered collections
+     where each subcollection is delimited by an element of the receiver
+     for which the given block evaluates to true.
+     The block is evaluated with a previous element of the collection 
+     and the following element"
+    
+    |str answer currentSubCollection currentElement previousElement|
+
+    str := self readStream.
+    answer := OrderedCollection new.
+    currentSubCollection := OrderedCollection new.
+    [ str atEnd ] whileFalse:[
+        currentElement := str next.
+        (previousElement notNil 
+         and:[aTwoArgBlock value:previousElement value:currentElement]) ifTrue:[
+            answer add:currentSubCollection.
+            currentSubCollection := OrderedCollection new
+        ].
+        currentSubCollection add:currentElement.
+        previousElement := currentElement.
+    ].
+    currentSubCollection notEmpty ifTrue:[
+        answer add:currentSubCollection
+    ].
+    ^ answer
+
+    "
+     #( 1 3 5 2 4 6 7 9 11 ) asCollectionOfSubCollectionsSeparatedByAnyChange:[:prev :curr | prev even ~= curr even].
+    "
+
+    "Created: / 17-03-2017 / 18:27:52 / stefan"
+!
+
+asCollectionOfSubCollectionsSeparatedByAnyForWhich:aBlock
+    "return a collection containing the subCollection
+     (separated by elements for which aBlock evaluates to true) of the receiver.
+     This allows breaking up strings using an arbitrary condition."
+
+    |words
+     start  "{ Class:SmallInteger }"
+     stop   "{ Class:SmallInteger }"
+     mySize "{ Class:SmallInteger }"|
+
+    words := self speciesForSubcollection new.
+    start := 1.
+    mySize := self size.
+    [start <= mySize] whileTrue:[
+        "skip multiple separators"
+        [ aBlock value:(self at:start)] whileTrue:[
+            start := start + 1 .
+            start > mySize ifTrue:[
+                ^ words
+            ].
+        ].
+
+        stop := self findFirst:aBlock startingAt:start.
+        stop == 0 ifTrue:[
+            words add:(self copyFrom:start to:mySize).
+            ^ words
+        ].
+        words add:(self copyFrom:start to:(stop - 1)).
+        start := stop
+    ].
+    ^ words
+
+    "
+     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:ch | ch = $:]
+     'h1e2l3l4o' asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:ch | ch isDigit]
+     #(1 9 2 8 3 7 4 6 5 5) asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:n | n odd]
+    "
+
+    "Modified (format): / 24-01-2017 / 18:57:57 / stefan"
+!
+
+asCollectionOfSubCollectionsSeparatedByAnyForWhich:aCheckBlock do:aBlock
+    "evaluate aBlock for each subcollection generated by separating elements
+     by elements for which aCheckBlock evaluates to true of the receiver.
+     This allows breaking up strings using an arbitrary condition."
+
+    |start  "{ Class:SmallInteger }"
+     stop   "{ Class:SmallInteger }"
+     mySize "{ Class:SmallInteger }"|
+
+    start := 1.
+    mySize := self size.
+    [start <= mySize] whileTrue:[
+        "skip multiple separators"
+        [ aCheckBlock value:(self at:start)] whileTrue:[
+            start := start + 1 .
+            start > mySize ifTrue:[
+                ^ self
+            ].
+        ].
+
+        stop := self findFirst:aCheckBlock startingAt:start.
+        stop == 0 ifTrue:[
+            aBlock value:(self copyFrom:start to:mySize).
+            ^ self
+        ].
+        aBlock value:(self copyFrom:start to:(stop - 1)).
+        start := stop
+    ].
+
+    "
+     'hello:world:isnt:this nice' asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:ch | ch = $:] do:[:component| Transcript showCR:component]
+     'h1e2l3l4o' asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:ch | ch isDigit]  do:[:component| Transcript showCR:component]
+     #(1 9 2 8 3 7 4 6 5 5) asCollectionOfSubCollectionsSeparatedByAnyForWhich:[:n | n odd]  do:[:component| Transcript showCR:component]
+    "
+
+    "Created: / 20-09-2017 / 19:03:35 / stefan"
+    "Modified: / 22-02-2019 / 10:06:27 / Stefan Vogel"
+!
+
+asStringWith:sepCharOrString
+    "return a string generated by concatenating my elements
+     (which must be strings or nil) and embedding sepCharOrString characters in between.
+     The argument sepCharOrString may be a character, a string or nil.
+     Nil entries and empty strings are counted as empty lines.
+     Similar to joinWith:, but specifically targeted towards collections of strings."
+
+    ^ self
+        from:1 to:(self size)
+        asStringWith:sepCharOrString
+        compressTabs:false
+        final:nil
+
+    "
+     #('hello' 'world' 'foo' 'bar' 'baz') asStringWith:$;
+     #('hello' 'world' 'foo' 'bar' 'baz') asStringWith:'|'
+     'hello|world|foo|bar|baz' asCollectionOfSubstringsSeparatedBy:$|
+    "
+
+    "Modified: / 10-07-2010 / 22:59:29 / cg"
+!
+
+asStringWith:sepCharacterOrString from:firstLine to:lastLine
+    "return part of myself as a string with embedded sepCharacters.
+     My elements must be strings or nil; nil entries and empty strings are
+     taken as empty lines.
+     The argument sepCharOrString may be a character, a string or nil.
+     Similar to joinWith:, but specifically targeted towards collections of strings."
+
+    ^ self
+        from:firstLine to:lastLine
+        asStringWith:sepCharacterOrString
+        compressTabs:false
+        final:nil
+    "
+     creating entries for searchpath:
+
+     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$;
+
+     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$: from:1 to:3
+    "
+
+    "Modified: 23.2.1996 / 15:28:55 / cg"
+!
+
+asStringWith:sepCharacterOrString from:firstLine to:lastLine compressTabs:compressTabs final:endCharacterOrString
+    "return part of myself as a string or text with embedded sepCharacters.
+     My elements must be strings or nil; nil entries and empty strings are
+     taken as empty lines.
+     The arguments sepCharacterOrString and endCharacterOrString may be nil, a character or a string.
+     If the argument compressTabs is true, leading spaces are converted
+     to tab-characters (8col tabs). The last line is followed by a final
+     character (if non-nil).
+     Similar to joinWith:, but specifically targeted towards collections of strings."
+
+    ^ self
+        from:firstLine to:lastLine
+        asStringWith:sepCharacterOrString
+        compressTabs:compressTabs
+        final:endCharacterOrString
+        withEmphasis:true
+
+    "Modified: / 17.6.1998 / 12:31:19 / cg"
+!
+
+asStringWith:sepCharacterOrString from:firstLine to:lastLine compressTabs:compressTabs final:endCharacterOrString withEmphasis:withEmphasis
+    "return part of myself as a string or text with embedded sepCharacters
+     and followup endCharacter.
+     My elements must be strings or nil; nil entries and empty strings are
+     taken as empty lines.
+     The arguments sepCharacterOrString and endCharacterOrString may be nil, a character or a string.
+     If the argument compressTabs is true, leading spaces are converted
+     to tab-characters (8col tabs). The last line is followed by a final
+     character (if non-nil).
+     The withEmphais argument controls if the returned string should preserve
+     any emphasis. If false, a plain string is returned.
+     This method is tuned for big collections, in not creating many
+     intermediate strings (has linear runtime). For very small collections
+     and small strings, it may be faster to use the comma , operation.
+     Similar to joinWith:, but specifically targeted towards collections of strings."
+
+    ^ self
+        from:firstLine to:lastLine
+        asStringWith:sepCharacterOrString
+        compressTabs:compressTabs
+        final:endCharacterOrString
+        withEmphasis:withEmphasis
+!
+
+asStringWithCRs
+    "return a string generated by concatenating my elements
+     (which must be strings or nil) and embedding cr characters in between.
+     Nil entries and empty strings are counted as empty lines."
+
+    ^ self asStringWithCRsFrom:1 to:(self size)
+
+    "
+     #('hello' 'world' 'foo' 'bar' 'baz') asStringWithCRs
+
+     (OrderedCollection new
+	add:'hello';
+	add:'world';
+	add:'foo';
+	add:('bar' asText allBold);
+	yourself) asStringWithCRs
+
+     Transcript showCR:
+	 (OrderedCollection new
+	    add:'hello';
+	    add:'world';
+	    add:'foo';
+	    add:('bar' asText allBold);
+	    yourself) asStringWithCRs
+    "
+
+    "Modified: 18.5.1996 / 16:43:47 / cg"
+!
+
+asStringWithCRsFrom:firstLine to:lastLine
+    "return a string generated by concatenating some of my elements
+     (which must be strings or nil) and embedding cr characters in between.
+     Nil entries and empty strings are counted as empty lines."
+
+    ^ self asStringWithCRsFrom:firstLine to:lastLine compressTabs:false withCR:true
+
+    "
+     #('hello' 'world' 'foo' 'bar' 'baz') asStringWithCRsFrom:2 to:4
+
+    "
+
+    "Modified: 18.5.1996 / 16:50:55 / cg"
+!
+
+asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs
+    "return part of myself as a string with embedded cr's.
+     My elements must be strings or nil.
+     If the argument compressTabs is true, leading spaces are converted
+     to tab-characters (8col tabs).
+     Nil entries and empty strings are taken as empty lines."
+
+    ^ self asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs withCR:true
+!
+
+asStringWithCRsFrom:firstLine to:lastLine compressTabs:compressTabs withCR:withCR
+    "return part of myself as a string with embedded cr's.
+     My elements must be strings or nil; nil entries and empty strings are
+     taken as empty lines.
+     If the argument compressTabs is true, leading spaces are converted
+     to tab-characters (8col tabs). WithCR controls whether the last line
+     should be followed by a cr or not."
+
+    ^ self 
+        asStringWith:(Character cr)
+        from:firstLine to:lastLine
+        compressTabs:compressTabs
+        final:(withCR ifTrue:[Character cr] ifFalse:[nil])
+!
+
+from:firstLine to:lastLine asStringWith:sepCharacterOrString
+    "return part of myself as a string with embedded sepCharacterOrStrings.
+     The argument sepCharacterOrString may be a character, a string or nil.
+     My elements must be strings or nil; nil entries and empty strings are
+     taken as empty lines."
+
+    ^ self
+        from:firstLine
+        to:lastLine
+        asStringWith:sepCharacterOrString
+        compressTabs:false
+        final:nil
+    "
+     creating entries for searchpath:
+
+     #('foo' 'bar' 'baz' '/foo/bar') asStringWith:$;
+
+     #('foo' 'bar' 'baz' '/foo/bar') from:1 to:3 asStringWith:$:
+
+     (#('foo' 'bar' 'baz' '/foo/bar') copyFrom:1 to:3) asStringWith:$:
+    "
+
+    "Modified: 23.2.1996 / 15:28:55 / cg"
+!
+
+from:firstLine to:lastLine asStringWith:sepCharacterOrString compressTabs:compressTabs final:endCharacterOrString
+    "return part of myself as a string or text with embedded sepCharacters.
+     My elements must be strings or nil; nil entries and empty strings are
+     taken as empty lines.
+     The arguments sepCharacterOrString and endCharacterOrString may be characters,
+     strings or nil.
+     If the argument compressTabs is true, leading spaces are converted
+     to tab-characters (8col tabs). 
+     The last line is followed by a final character (if non-nil)."
+
+    ^ self
+        from:firstLine
+        to:lastLine
+        asStringWith:sepCharacterOrString 
+        compressTabs:compressTabs
+        final:endCharacterOrString 
+        withEmphasis:true
+
+    "Modified: / 17.6.1998 / 12:31:19 / cg"
+!
+
+joinWithAll:separatingCollection
+    "return a collection generated by concatenating my elements
+     and slicing separatingCollection in between.
+     Similar to asStringWith:, but not specifically targeted towards collections of strings."
+
+    ^ self
+        joinWithAll:separatingCollection
+        from:1 to:(self size) as:nil
+
+    "
+     #('hello' 'world' 'foo' 'bar' 'baz') joinWithAll:' ; '   
+     #('hello' 'world' 'foo' 'bar' 'baz') joinWithAll:' | '
+    "
+!
+
+joinWithAll:separatingCollection from:startIndex to:endIndex as:speciesOrNil 
+    "extract parts of myself as a new collection with optional embedded separator.
+     Separator may be nil, or a collection of elements to be sliced in between.
+     SpeciesOrNil specifies the species of the resultig object, allowing for Arrays to be converted
+     as OrderedCollection or vice versa on the fly. If nil is passed in, the species of the first non-nil
+     element is used.
+     This counts the overall size first, then allocates the new collection once and replaces elements
+     via bulk copies. For very small collections, it may be faster to use the comma , operation.
+     Similar to asStringWith:, but not specifically targeted towards string handling."
+
+    |totalLength "{ Class:SmallInteger }"
+     pos         "{ Class:SmallInteger }"
+     sepCnt      "{ Class:SmallInteger }"
+     subColl newColl 
+     species|
+
+    startIndex = endIndex ifTrue:[ ^ self at:startIndex ].
+
+    species := speciesOrNil.
+
+    "
+     first accumulate the size of the result, 
+     to avoid countless reallocations.
+    "
+    totalLength := 0.
+    sepCnt := separatingCollection size.
+
+    startIndex to:endIndex do:[:index |
+        subColl := self at:index.
+        totalLength := totalLength + subColl size.
+        species isNil ifTrue:[
+            subColl notNil ifTrue:[
+                species := subColl species
+            ]
+        ]
+    ].
+    totalLength := totalLength + ((endIndex - startIndex) * sepCnt).
+    newColl := species newWithSize:totalLength.
+
+    pos := 1.
+    startIndex to:endIndex do:[:index |
+        subColl := self at:index.
+        subColl size ~~ 0 ifTrue:[
+            newColl replaceFrom:pos with:subColl startingAt:1.
+            pos := pos + subColl size.
+        ].
+        ((sepCnt ~~ 0) and:[index ~~ endIndex]) ifTrue:[
+            newColl replaceFrom:pos to:(pos+sepCnt-1) with:separatingCollection startingAt:1.
+            pos := pos + sepCnt.
+        ].
+    ].
+
+    ^ newColl
+
+    "
+     #( 'aa' 'bb' '' 'cc' ) joinWith:'|' from:1 to:4 as:String  
+     #( 'aa' 'bb' '' 'cc' ) joinWith:nil from:1 to:4 as:String  
+     #( 'aa' 'bb' '' 'cc' ) joinWith:'|' from:1 to:4 as:Array   
+     #( (1 2 3) (4 5 6) (7 6 8) ) joinWith:#(nil) from:1 to:3 as:OrderedCollection  
+     #( (1 2 3) (4 5 6) (7 6 8) ) joinWith:nil from:1 to:3 as:nil                
+    "
+
+    "Created: / 17.6.1998 / 12:30:32 / cg"
+    "Modified: / 17.6.1998 / 12:31:59 / cg"
+!
+
+split:aCollection indicesDo:aTwoArgBlock
+    "Split a collection by myself as a delimiter.
+     see Object >> split: for optimized version for single delimiters.
+     Example:
+        '||' split: 'foo||bar||2'"
+
+    |position oldPosition|
+
+    position := 1.
+    oldPosition := position.
+    position := aCollection indexOfSubCollection:self startingAt:position.
+    [position ~~ 0] whileTrue:[
+        aTwoArgBlock value:oldPosition value:position-1.
+        position := position + self size.
+        oldPosition := position.
+        position := aCollection indexOfSubCollection:self startingAt:position.        
+    ].
+    aTwoArgBlock value:oldPosition value:aCollection size
+    
+    "
+     'xx' split:'helloxxworldxxthisxxisxxsplitted' indicesDo: [:start :stop | Transcript show:start; show:' to '; showCR:stop ]
+     'xx' split:'helloxxworldxxthisxxisxxsplitted' do: [:frag | Transcript showCR:frag ]
+
+     'hello world' 
+        splitOn: ' ' 
+        do: [:part | Transcript showCR:part ]
+    "
+    
+    "
+     'hello world' 
+        splitOn: ' ' 
+        indicesDo: [:start :stop | Transcript show:start; show:' to '; showCR:stop ]
+    "
+
+    "Created: / 13-07-2017 / 16:46:58 / cg"
+    "Modified (comment): / 13-07-2017 / 18:39:05 / cg"
+    "Modified: / 30-07-2018 / 09:03:26 / Stefan Vogel"
+!
+
+splitBy:anElement do:aBlock
+    "evaluate aBlock for each subcollection generated by separating elements
+     of the receiver by anElement.
+     If anElement occurs multiple times in a row,
+     the block will be invoked with empty collections as argument.
+     This algorithm uses equality-compare to detect the element."
+
+    ^ self asCollectionOfSubCollectionsSeparatedBy:anElement do:aBlock
+
+    "
+     '' 
+        splitBy:$: do:[:each | Transcript showCR:each storeString]
+
+     '1 one' 
+        splitBy:$: do:[:each | Transcript showCR:each storeString]
+
+     '1 one:2 two:3 three:4 four:5 five' 
+        splitBy:$: do:[:each | Transcript showCR:each storeString]
+
+     'a::b' 
+        splitBy:$: do:[:each | Transcript showCR:each storeString]
+
+     ':' 
+        splitBy:$: do:[:each | Transcript showCR:each storeString]
+
+     ':a' 
+        splitBy:$: do:[:each | Transcript showCR:each storeString]
+
+     'a:' 
+        splitBy:$: do:[:each | Transcript showCR:each storeString]
+    "
+!
+
+splitByAny:aCollectionOfSeparators
+    "return a collection containing the subCollection
+     (separated by any from aCollectionOfSeparators) of the receiver.
+     This allows breaking up strings using a number of elements as separator.
+     Uses equality-compare when searching for separators."
+
+    ^ self asCollectionOfSubCollectionsSeparatedByAny:aCollectionOfSeparators
+
+    "
+     'hello:world:isnt:this nice' splitByAny:#($:)
+     'hello:world:isnt:this nice' splitByAny:':'
+     'hello:world:isnt:this nice' splitByAny:(Array with:$: with:Character space)
+     'hello:world:isnt:this nice' splitByAny:#( $: $ ) 
+     'hello:world:isnt:this nice' splitByAny:{ $: . $ }
+     'hello:world:isnt:this nice' splitByAny:': '
+     'h1e2l3l4o' splitByAny:($1 to: $9)
+     #(1 9 2 8 3 7 4 6 5 5) splitByAny:#(1 2 3)
+    "
+!
+
+splitForSize:pieceSize
+    "slice into pieces; return a collection containing pieces of size pieceSize from the receiver.
+     The last piece may be smaller, if the receiver's size is not a multiple of pieceSize."
+
+    ^ self asCollectionOfSubCollectionsOfSize:pieceSize
+
+    "
+     '123123123123123123' splitForSize:3 
+     '12312312312312312312' splitForSize:3 
+    "
+!
+
+splitOn:splitter
+    "Split at any encounter of splitter in the receiver.
+     splitter can be any object which implements #split:;
+     in particular, Strings, Regexes and Blocks can be used as spitter.
+     Any other object used as splitter is treated as an element 
+     used as split object (i.e. I wil split at that element).
+     If the splitter is not encountered, a single element collection containing
+     the receiver is returned"
+
+    ^ splitter split:self
+
+    "
+     'hello world' splitOn:' '
+     'abacadae' splitOn:$a
+     'abacadae' splitOn:'a'
+     'abaacaadaae' splitOn:'aa'
+     'abaacaadaae' splitOn:[:ch | ch == $a]
+     'abaacaadaae' splitOn:('a+' asRegex)
+     'helloworld' splitOn:' '        
+     'helloworld ' splitOn:' '       
+     ' helloworld ' splitOn:' '      
+
+     #(0 1 2 3 1 4 5 6 1 7 1 9 10) splitOn:1
+    "
+
+    "Created: / 13-07-2017 / 16:37:44 / cg"
+!
+
+splitOn:splitter do:aBlock
+    "split the receiver using splitter (can be a string or regex),
+     and evaluate aBlock on each fragment.
+     splitter can be any object which implements #split:;
+     in particular, Strings, Regexes and Blocks can be
+     used as spitter.
+     Any other object used as splitter is treated as an Array 
+     containing that split object"
+
+    ^ splitter split:self do:aBlock
+
+    "
+     'hello world' 
+        splitOn:' ' 
+        do:[:fragment | Transcript showCR:fragment].
+    "
+
+    "Created: / 13-07-2017 / 16:38:35 / cg"
+!
+
+splitOn:splitter indicesDo:aTwoArgBlock
+    "split the receiver using splitter (can be a string or regex),
+     and evaluate aTwoArgBlock on each pair of start- and stop index.
+     Splitter can be any object which implements #split:;
+     in particular, Strings, Regexes and Blocks can be used.
+     Any other splitter object is treated as an Array 
+     containing that split object"
+
+    ^ splitter split:self indicesDo:aTwoArgBlock
+
+    "
+     'hello world' 
+        splitOn:' ' 
+        indicesDo: [:start :stop | Transcript show:start; show:' to '; showCR:stop ]
+    "
+
+    "Created: / 13-07-2017 / 16:48:47 / cg"
+!
+
+splitOnFirst:splitter
+    "Split at the first encounter of splitter in the receiver;
+     return the two parts or nil, if the splitter was not encountered.
+     splitter can be any object which implements #split:;
+     in particular, Strings, Regexes and Blocks can be used as spitter.
+     Any other object used as splitter is treated as an element 
+     used as split object (i.e. I wil split at that element).
+     Returns a two-element collection containing the left and right parts.
+     If the splitter is not encountered, the returned right part is nil.
+     If the splitter is encountered at the end, the returned right part is empty"
+
+    splitter splitFirstIn:self do:[:leftPart :rightPart | ^ {leftPart . rightPart}].
+    ^ nil
+
+    "
+     'hello world more there' splitOnFirst:' ' 
+     'bacadae' splitOnFirst:$a               
+     'abaacaadaae' splitOnFirst:'aa'         
+     'baacAadaae' splitOnFirst:[:ch | ch isUppercase]  
+     'abaacaadaae' splitOnFirst:('a+' asRegex)
+     'helloworld' splitOnFirst:' '  
+     'helloworld ' splitOnFirst:' '       
+
+     #(1 2 true 3 4 5) splitOnFirst:true     
+    "
+
+    "Created: / 13-07-2017 / 16:37:44 / cg"
+! !
+
 !SequenceableCollection methodsFor:'testing'!
 
 includesKey:anIndex
     "return true, if anIndex is a valid key.
      NOTICE: in ST-80, this message is only defined for Dictionaries,
-	     however, having a common protocol with indexed collections
-	     often simplifies things."
+             however, having a common protocol with indexed collections
+             often simplifies things."
 
     anIndex isInteger ifFalse:[^ false].
-    ^ (anIndex >= 1) and:[anIndex <= self size]
+    ^ (anIndex > 0) and:[anIndex <= self size]
 
     "
      #(1 2 3) includesKey:4
      #(1 2 3) includesKey:3
+     #(1 2 3) includesKey:0
     "
 ! !
 
@@ -10429,7 +12059,7 @@
 
     mySize := self size.
     mySize = aFloatVector size ifFalse:[
-        ^ self error:'Must be of equal size'
+        ^ ArgumentError raiseErrorString:'Vector be of equal size'
     ].
     result := 0.0.
     1 to: mySize do:[:i|
@@ -10446,10 +12076,14 @@
      v := #(2.0 2.0 1.0) asDoubleArray.
      v dot:v.            
     "
+
+    "Modified: / 06-06-2019 / 23:23:48 / Claus Gittinger"
 !
 
 hornerMultiplyAndAdd:x
-    "fallback for horner's-method computation of polynomials.
+    "horner's-method computation of polynomials.
+     (this is a fallback - there are highspeed versions in the floatArray subclasses.
+
      The vector is interpreted as providing the factors for a polynomial,
         an*x^n + (an-1)*x^(n-1) + ... + a2(x) + a1
      where the ai are the elements of the Array.
@@ -10537,5 +12171,3 @@
     ^ '$Changeset: <not expanded> $'
 ! !
 
-
-SequenceableCollection initialize!
--- a/String.st	Mon Aug 31 11:59:30 2020 +0100
+++ b/String.st	Mon Aug 31 12:01:25 2020 +0100
@@ -2,8 +2,6 @@
 
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
- COPYRIGHT (c) 2015 Jan Vrany
- COPYRIGHT (c) 2018 Jan Vrany
 	      All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -27,24 +25,31 @@
 !String primitiveDefinitions!
 %{
 
-#include <stdio.h>
-#define _STDIO_H_INCLUDED_
-#include <stdlib.h>
-#include <ctype.h>
+#ifndef _STDIO_H_INCLUDED_
+# include <stdio.h>
+# define _STDIO_H_INCLUDED_
+#endif
+
+#ifndef _STDLIB_H_INCLUDED_
+# include <stdlib.h>
+# define _STDLIB_H_INCLUDED_
+#endif
+
+#ifndef _CTYPE_H_INCLUDED_
+# include <ctype.h>
+# define _CTYPE_H_INCLUDED_
+#endif
 
 #ifdef LINUX
 # define __STRINGDEFS__
 # include <linuxIntern.h>
 #endif
 
-#ifdef __osx__
-# include <string.h>
-# include <stdlib.h>
-#endif
-
-#ifdef __MINGW__
-# include <string.h>
-# include <stdlib.h>
+#if defined(__osx__) || defined(__MINGW__)
+# ifndef _STRING_H_INCLUDED_
+#  include <string.h>
+#  define _STRING_H_INCLUDED_
+# endif
 #endif
 
 /*
@@ -54,6 +59,11 @@
  */
 #define INITIALIZE_WITH_SPACE
 
+#ifdef FAST_MEMCHR
+// # if !defined(__osx__) && !defined(__win32__)
+// extern void *memchr();
+// # endif
+#endif
 %}
 ! !
 
@@ -112,8 +122,6 @@
 copyright
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
- COPYRIGHT (c) 2015 Jan Vrany
- COPYRIGHT (c) 2018 Jan Vrany
 	      All Rights Reserved
 
  This software is furnished under a license and may be used
@@ -131,16 +139,16 @@
 
     Strings are kind of kludgy: to allow for easy handling by C functions,
     there is always one 0-byte added at the end, which is not counted
-    in the strings size, and is not accessible from the smalltalk level.
-    This guarantees, that a smalltalk string can always be passed to a
-    C- or a system api function without danger (of course, this does not
-    prevent a nonsense contents ...)
+    in the string's size, and is not accessible from the Smalltalk level.
+    This guarantees, that a Smalltalk string can always be passed to a
+    C- or a system api function without danger 
+    (of course, this does not prevent a nonsense contents...)
 
     You cannot add any instvars to String, since the run time system & compiler
     creates literal strings and knows that strings have no named instvars.
     If you really need strings with instVars, you have to create a subclass
     of String (the access functions defined here can handle this).
-    A little warning though: not all smalltalk systems allow subclassing String,
+    A little warning though: not all Smalltalk systems allow subclassing String,
     so your program may become unportable if you do so.
 
     Strings have an implicit (assumed) encoding of ISO-8859-1.
@@ -153,11 +161,11 @@
     processing a String containing the 0-byte.
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 
     [see also:]
-	Text StringCollection TwoByteString JISEncodedString
-	Symbol
+        Text StringCollection TwoByteString JISEncodedString
+        Symbol
 "
 ! !
 
@@ -179,117 +187,98 @@
     REGISTER unsigned char *cp;
     int nInstVars;
 
+    // fetch first; check later
+    // (if not a smallInteger, value will be ignored anyway)
+    len = __intVal(anInteger);
+    instsize = OHDR_SIZE + len + 1;
     if (__isSmallInteger(anInteger)) {
-	len = __intVal(anInteger);
-	if (len >= 0) {
-	    instsize = OHDR_SIZE + len + 1;
-	    if (self == String || self == ImmutableString) {
-		if (__CanDoQuickNew(instsize)) {        /* OBJECT ALLOCATION */
-		    /*
-		     * the most common case
-		     */
-		    __qCheckedNew(newString, instsize);
-		    __InstPtr(newString)->o_class = self; /* no need for PROTECT - there was no GC */
-		    __qSTORE(newString, self);
-
-		    cp = __stringVal(newString);
-
+        if (len >= 0) {
+            if (self == String || self == ImmutableString) {
+                if (__CanDoQuickNew(instsize)) {        /* OBJECT ALLOCATION */
+                    /*
+                     * the most common case
+                     */
+                    __qCheckedNew(newString, instsize);
+                    __InstPtr(newString)->o_class = self; /* no need for PROTECT - there was no GC */
+                    __qSTORE(newString, self);
+
+                    cp = __stringVal(newString);
+                fillIt:
+                    // fill bytes at cp
 # if defined(memset4)
-		    {
-			/*
-			 * no sizeof(int) here please -
-			 * - memset4 (if defined) fills 4-bytes on ALL machines
-			 */
-			int l4 = len >> 2;
-
-			if (len & 3) l4++;
-			memset4(cp, 0x20202020, l4);
-			cp[len] = '\0';
-		    }
+                    {
+                        /*
+                         * no sizeof(int) here please -
+                         * - memset4 (if defined) fills 4-bytes on ALL machines
+                         */
+                        int l4 = len >> 2;
+
+                        if (len & 3) l4++;
+                        memset4(cp, 0x20202020, l4);
+                        cp[len] = '\0';
+                    }
 # else
 #  ifdef FAST_MEMSET
-		    memset(cp, ' ', len);
-		    cp[len] = '\0';
+                    memset(cp, ' ', len);
+                    cp[len] = '\0';
 #  else
-		    for ( ; len >= 8; cp += 8, len -= 8) {
+                    for ( ; len >= 8; cp += 8, len -= 8) {
 #   ifdef INT64
-			((INT64 *)cp)[0] = 0x2020202020202020L;
+                        ((INT64 *)cp)[0] = 0x2020202020202020L;
 #   else
-			((int *)cp)[0] = 0x20202020;
-			((int *)cp)[1] = 0x20202020;
+                        ((int *)cp)[0] = 0x20202020;
+                        ((int *)cp)[1] = 0x20202020;
 #   endif
-		    }
-		    while (len--)
-			*cp++ = ' ';
-		    *cp = '\0';
+                    }
+                    while (len--)
+                        *cp++ = ' ';
+                    *cp = '\0';
 #  endif /* not FAST_MEMSET */
 # endif /* not memset4 */
 
-		    RETURN (newString);
-		}
-		nInstVars = 0;
-	    } else {
-		nInstVars = __intVal(__ClassInstPtr(self)->c_ninstvars);
-		instsize += __OBJS2BYTES__(nInstVars);
-	    }
-
-	    __PROTECT_CONTEXT__;
-	    __qNew(newString, instsize);        /* OBJECT ALLOCATION */
-	    __UNPROTECT_CONTEXT__;
-
-	    if (newString == nil) goto fail;
-
-	    __InstPtr(newString)->o_class = self;
-	    __qSTORE(newString, self);
-
-	    cp = __stringVal(newString);
-	    if (nInstVars) {
-		OBJ *op;
-		cp += __OBJS2BYTES__(nInstVars);
-
-		/*
-		 * nil-out instvars
-		 */
+                    RETURN (newString);
+                }
+                nInstVars = 0;
+            } else {
+                nInstVars = __intVal(__ClassInstPtr(self)->c_ninstvars);
+                instsize += __OBJS2BYTES__(nInstVars);
+            }
+
+            __PROTECT_CONTEXT__;
+            __qNew(newString, instsize);        /* OBJECT ALLOCATION */
+            __UNPROTECT_CONTEXT__;
+
+            if (newString == nil) goto fail;
+
+            __InstPtr(newString)->o_class = self;
+            __qSTORE(newString, self);
+
+            cp = __stringVal(newString);
+            if (nInstVars) {
+                OBJ *op;
+                cp += __OBJS2BYTES__(nInstVars);
+
+                /*
+                 * nil-out instvars
+                 */
 # if defined(memset4)
-		memset4(__InstPtr(newString)->i_instvars, nil, nInstVars);
+                memset4(__InstPtr(newString)->i_instvars, nil, nInstVars);
 # else
 #  if defined(FAST_MEMSET) && ! defined(NEGATIVE_ADDRESSES)
-		/*
-		 * knowing that nil is 0
-		 */
-		memset(__InstPtr(newString)->i_instvars, 0, __OBJS2BYTES__(nInstVars));
+                /*
+                 * knowing that nil is 0
+                 */
+                memset(__InstPtr(newString)->i_instvars, 0, __OBJS2BYTES__(nInstVars));
 #  else
-		op = __InstPtr(newString)->i_instvars;
-		do {
-		    *op++ = nil;
-		} while (--nInstVars);
+                op = __InstPtr(newString)->i_instvars;
+                do {
+                    *op++ = nil;
+                } while (--nInstVars);
 #  endif  /* !FAST_MEMSET */
 # endif
-	    }
-
-	    /*
-	     * fill with spaces
-	     */
-# ifdef FAST_MEMSET
-	    memset(cp, ' ', len);
-	    *(cp + len) = '\0';
-# else
-	    while (len >= 8) {
-#  ifdef INT64
-		((INT64 *)cp)[0] = 0x2020202020202020L;
-#  else
-		((int *)cp)[0] = 0x20202020;
-		((int *)cp)[1] = 0x20202020;
-#  endif
-		cp += 8;
-		len -= 8;
-	    }
-	    while (len--)
-		*cp++ = ' ';
-	    *cp = '\0';
-# endif /* !FAST_MEMSET */
-	    RETURN (newString);
-	}
+            }
+            goto fillIt;
+        }
     }
 fail: ;;
 #endif /* not __SCHTEAM__ */
@@ -299,14 +288,16 @@
      use error handling in superclass
     "
     (anInteger < 0) ifTrue:[
-	"
-	 the argument is negative,
-	"
-	self error:'bad (negative) argument to new:'.
-	^ nil
+        "
+         the argument is negative,
+        "
+        self argumentError:'bad (negative) argument to new:' with:anInteger.
+        ^ nil
     ].
 
     ^ (super basicNew:anInteger+1) atAllPut:(Character space)
+
+    "Modified: / 24-03-2019 / 10:07:43 / Claus Gittinger"
 !
 
 new:n
@@ -363,65 +354,67 @@
     REGISTER OBJ *op;
     int nInstVars, instsize;
 
+    // fetch first; check later
+    // (if not a smallInteger, value will be ignored anyway)
+    len = __intVal(anInteger);
+    instsize = OHDR_SIZE + len + 1;
     if (__isSmallInteger(anInteger)) {
-	len = __intVal(anInteger);
-	if (len >= 0) {
-	    instsize = OHDR_SIZE + len + 1;
-	    if (self == String) {
-		if (__CanDoQuickNew(instsize)) {        /* OBJECT ALLOCATION */
-		    /*
-		     * the most common case
-		     */
-		    __qCheckedNew(newString, instsize);
-		    __InstPtr(newString)->o_class = self; /* no need for PROTECT - there was no GC */
-		    __qSTORE(newString, self);
-
-		    cp = __stringVal(newString);
-		    cp[len] = '\0';
-		    RETURN (newString);
-		}
-		nInstVars = 0;
-	    } else {
-		nInstVars = __intVal(__ClassInstPtr(self)->c_ninstvars);
-		instsize += __OBJS2BYTES__(nInstVars);
-	    }
-
-	    __PROTECT_CONTEXT__;
-	    __qNew(newString, instsize);        /* OBJECT ALLOCATION */
-	    __UNPROTECT_CONTEXT__;
-
-	    if (newString == nil) goto fail;
-
-	    __InstPtr(newString)->o_class = self;
-	    __qSTORE(newString, self);
-
-	    if (nInstVars) {
-		/*
-		 * nil-out instvars
-		 */
+        if (len >= 0) {
+            if (self == String) {
+                if (__CanDoQuickNew(instsize)) {        /* OBJECT ALLOCATION */
+                    /*
+                     * the most common case
+                     */
+                    __qCheckedNew(newString, instsize);
+                    __InstPtr(newString)->o_class = self; /* no need for PROTECT - there was no GC */
+                    __qSTORE(newString, self);
+
+                    cp = __stringVal(newString);
+                    cp[len] = '\0';
+                    RETURN (newString);
+                }
+                nInstVars = 0;
+            } else {
+                nInstVars = __intVal(__ClassInstPtr(self)->c_ninstvars);
+                instsize += __OBJS2BYTES__(nInstVars);
+            }
+
+            __PROTECT_CONTEXT__;
+            __qNew(newString, instsize);        /* OBJECT ALLOCATION */
+            __UNPROTECT_CONTEXT__;
+
+            if (newString == nil) goto fail;
+
+            __InstPtr(newString)->o_class = self;
+            __qSTORE(newString, self);
+
+            if (nInstVars) {
+                /*
+                 * nil-out instvars
+                 */
 # if defined(memset4)
-		memset4(__InstPtr(newString)->i_instvars, nil, nInstVars);
+                memset4(__InstPtr(newString)->i_instvars, nil, nInstVars);
 # else
 #  if defined(FAST_MEMSET) && ! defined(NEGATIVE_ADDRESSES)
-		/*
-		 * knowing that nil is 0
-		 */
-		memset(__InstPtr(newString)->i_instvars, 0, __OBJS2BYTES__(nInstVars));
+                /*
+                 * knowing that nil is 0
+                 */
+                memset(__InstPtr(newString)->i_instvars, 0, __OBJS2BYTES__(nInstVars));
 #  else
-		op = __InstPtr(newString)->i_instvars;
-		do {
-		    *op++ = nil;
-		} while (--nInstVars);
+                op = __InstPtr(newString)->i_instvars;
+                do {
+                    *op++ = nil;
+                } while (--nInstVars);
 #  endif
 # endif
-		cp = __stringVal(newString) + __OBJS2BYTES__(nInstVars);
-	    } else {
-		cp = __stringVal(newString);
-	    }
-
-	    *(cp + len) = '\0';
-	    RETURN (newString);
-	}
+                cp = __stringVal(newString) + __OBJS2BYTES__(nInstVars);
+            } else {
+                cp = __stringVal(newString);
+            }
+
+            cp[len] = '\0';
+            RETURN (newString);
+        }
     }
 fail: ;;
 #endif /* not __SCHTEAM__ */
@@ -431,11 +424,11 @@
      use error handling in superclass
     "
     (anInteger < 0) ifTrue:[
-	"
-	 the argument is negative,
-	"
-	self error:'bad (negative) argument to new:'.
-	^ nil
+        "
+         the argument is negative,
+        "
+        self argumentError:'bad (negative) argument to new:' with:anInteger.
+        ^ nil
     ].
 
     ^ self basicNew:anInteger
@@ -443,6 +436,8 @@
     "
      String uninitializedNew:100
     "
+
+    "Modified: / 24-03-2019 / 10:08:04 / Claus Gittinger"
 ! !
 
 !String class methodsFor:'Compatibility-Dolphin'!
@@ -456,16 +451,19 @@
 !String class methodsFor:'Compatibility-Squeak'!
 
 cr
+    <resource: #obsolete>
     "return a string consisting of the cr-Character"
 
     "/ ATTENTION: you get a NL (for compatibility) here!!
     "/ please use String return  / String lf
-    self halt:'please make it explicit, if a return or a linefeed is wanted.'.
+"/    self obsoleteMethodWarning:'please make it explicit, if a return or a linefeed is wanted.'.
     "/ for now.
     "/ will be changed, when the historic UNIX baggage is removed
     "/ and all cr's are really returns (instead of nl's).
 
     ^ self lf
+
+    "Modified: / 31-03-2020 / 11:23:37 / Stefan Vogel"
 !
 
 crlf
@@ -497,6 +495,14 @@
     ^ CR
 !
 
+space
+    "return a string consisting of a single space Character"
+
+    ^ ' '
+
+    "Created: / 13-07-2017 / 12:46:21 / cg"
+!
+
 stringHash:aString initialHash:speciesHash
     "for squeak compatibility only; this is NOT the same hash as my instances use"
 
@@ -524,6 +530,7 @@
 
 
 
+
 !String class methodsFor:'queries'!
 
 defaultPlatformClass
@@ -544,6 +551,10 @@
 ! !
 
 
+
+
+
+
 !String methodsFor:'accessing'!
 
 at:index
@@ -559,23 +570,20 @@
 	return context._RETURN( self.basicAt( idx1Based ));
     }
 #else
-    REGISTER INT indx;
+    REGISTER int indx;
     REGISTER OBJ slf, cls;
 
     if (__isSmallInteger(index)) {
 	slf = self;
 	cls = __qClass(slf);
 	indx = __intVal(index) - 1;
-	if (cls == String) {
-	    fetch:
-	    if ((unsigned INT)indx < (unsigned)(__stringSize(slf))) {
-	        RETURN ( __MKCHARACTER(__stringVal(slf)[indx] & 0xFF) );
-	    }	    
-	   goto badIndex;
-        }
-	if (indx < 0) goto badIndex;
-	indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-	goto fetch;
+	if (cls != String) {
+	    if (indx < 0) goto badIndex;
+	    indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+	}
+	if ((unsigned)indx < (unsigned)(__stringSize(slf))) {
+	    RETURN ( __MKCHARACTER(__stringVal(slf)[indx] & 0xFF) );
+	}
     }
 badIndex: ;
 #endif /* ! __SCHTEAM__ */
@@ -593,10 +601,10 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     if (index.isSmallInteger()) {
-	int idx1Based = index.intValue();   // st index is 1 based
-
-	self.basicAt_put(idx1Based, aCharacter );
-	return context._RETURN( aCharacter );
+        int idx1Based = index.intValue();   // st index is 1 based
+
+        self.basicAt_put(idx1Based, aCharacter );
+        return context._RETURN( aCharacter );
     }
 #else
     REGISTER int value, indx;
@@ -604,22 +612,28 @@
 
     slf = self;
 
+    /* not __isStringLike here, because that includes Symbol and ImmutableString,
+     * which are not writable
+    */
     if (__isString(slf)) {
-	if (__isCharacter(aCharacter)) {
-	    value = __intVal(__characterVal(aCharacter));
-	    if (((unsigned)value <= 0xFF)
-	     && __isSmallInteger(index)) {
-		indx = __intVal(index) - 1;
-		if ((unsigned INT)indx < (unsigned)(__stringSize(slf))) {
-		    __stringVal(slf)[indx] = value;
-		    RETURN ( aCharacter );
-		}
-	    }
-	}
+        if (__isCharacter(aCharacter)) {
+            value = __intVal(__characterVal(aCharacter));
+            if (((unsigned)value <= 0xFF)
+             && __isSmallInteger(index)) {
+                indx = __intVal(index) - 1;
+                if ((unsigned)indx < (unsigned)(__stringSize(slf))) {
+                    __stringVal(slf)[indx] = value;
+                    RETURN ( aCharacter );
+                }
+            }
+        }
     }
 #endif /* ! __SCHTEAM__ */
 %}.
     ^ self basicAt:index put:aCharacter
+
+    "Modified: / 22-03-2019 / 03:04:21 / Claus Gittinger"
+    "Modified: / 15-11-2019 / 17:37:42 / Stefan Vogel"
 !
 
 basicAt:index
@@ -633,7 +647,7 @@
 	return context._RETURN( self.basicAt( idx1Based ));
     }
 #else
-    REGISTER INT indx;
+    REGISTER int indx;
     REGISTER OBJ slf, cls;
 
     if (__isSmallInteger(index)) {
@@ -644,7 +658,7 @@
 	    if (indx < 0) goto badIndex;
 	    indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
 	}
-	if ((unsigned INT)indx < (unsigned)(__stringSize(slf))) {
+	if ((unsigned)indx < (unsigned)(__stringSize(slf))) {
 	    RETURN ( __MKCHARACTER(__stringVal(slf)[indx] & 0xFF) );
 	}
     }
@@ -690,7 +704,7 @@
 		if (indx < 0) goto badIndex;
 		indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
 	    }
-	    if ((unsigned INT)indx < (unsigned)(__stringSize(slf))) {
+	    if ((unsigned)indx < (unsigned)(__stringSize(slf))) {
 		__stringVal(slf)[indx] = value;
 		RETURN ( aCharacter );
 	    }
@@ -730,7 +744,7 @@
 
 %{  /* NOCONTEXT */
 
-    REGISTER INT indx;
+    REGISTER int indx;
     REGISTER OBJ slf, cls;
 
     slf = self;
@@ -740,7 +754,7 @@
 	if (indx < 0) goto badIndex;
 	indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
     }
-    if ((unsigned INT)indx < (unsigned)(__stringSize(slf))) {
+    if ((unsigned)indx < (unsigned)(__stringSize(slf))) {
 	RETURN ( __MKCHARACTER(__stringVal(slf)[indx] & 0xFF) );
     }
 badIndex: ;
@@ -1440,7 +1454,7 @@
 !
 
 indexOfNonSeparatorStartingAt:start
-    "return the index of the next non-whiteSpace character"
+    "return the index of the next non-whiteSpace character, 0 if none found"
 
 %{  /* NOCONTEXT */
 
@@ -1481,10 +1495,12 @@
      'hello world' indexOfNonWhiteSpaceStartingAt:3
      'hello world' indexOfNonWhiteSpaceStartingAt:7
     "
+
+    "Modified: / 01-03-2017 / 15:25:40 / cg"
 !
 
 indexOfSeparatorStartingAt:start
-    "return the index of the next separator character"
+    "return the index of the next separator (whitespace) character; 0 if none found"
 
 %{  /* NOCONTEXT */
 
@@ -1627,6 +1643,8 @@
      with 4-byte at a time: 640 640 620
      with 8-byte at a time: 280 290 300
     "
+
+    "Modified: / 01-03-2017 / 15:26:01 / cg"
 !
 
 occurrencesOf:aCharacter
@@ -1950,6 +1968,100 @@
     ^ super > aString
 !
 
+compareCaselessWith:aString
+    "Compare the receiver against the argument, ignoring case.
+     Return 1 if the receiver is greater, 0 if equal and -1 if less than the argument."
+
+%{  /* NOCONTEXT */
+
+    int cmp;
+
+    if (__isNonNilObject(aString)) {
+        int argIsString = __qIsStringLike(aString);
+
+        if (argIsString || __qClass(aString) == __qClass(self)) {
+            unsigned char *cp1, *cp2;
+            unsigned char ch1, ch2;
+
+            //
+            // care for instances of subclasses ...
+            //
+            cp1 = __stringVal(self);
+            if (!__qIsStringLike(self)) {
+                int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+
+                cp1 += n;
+            }
+
+            //
+            // care for instances of subclasses ...
+            //
+            cp2 = __stringVal(aString);
+            if (!argIsString) {
+                int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(aString))->c_ninstvars));
+
+                cp2 += n;
+            }
+
+            while (1) {
+                while ((ch1 = *cp1++) == (ch2 = *cp2++)) {
+                    if (ch1 == 0) {
+                        RETURN( __mkSmallInteger( 0 ) );
+                    }
+                }
+                    
+                // first difference
+                if (ch1 == 0) {
+                    // receiver shorter
+                    RETURN( __mkSmallInteger( -1 ) );
+                }
+                if (ch2 == 0) {
+                    // arg shorter
+                    RETURN( __mkSmallInteger( 1 ) );
+                }
+
+                if (((ch1 >= 'A') && (ch1 <= 'Z'))
+                 || ((ch1 >= 0xC0) && (ch1 <= 0xDE) && (ch1 != 0xD7))) {
+                    ch1 += 'a'-'A';
+                }    
+                if (((ch2 >= 'A') && (ch2 <= 'Z'))
+                 || ((ch2 >= 0xC0) && (ch2 <= 0xDE) && (ch2 != 0xD7))) {
+                    ch2 += 'a'-'A';
+                }
+                if (ch1 != ch2) {
+                    if (ch1 < ch2) {
+                        RETURN( __mkSmallInteger( -1 ) );
+                    }
+                    RETURN( __mkSmallInteger( 1 ) );
+                }
+            }
+        }
+    }
+getOutOfHere: ;
+%}.
+    "
+     currently, this operation is only defined for strings, symbols and subclasses.
+     allow for an implementation in Smalltalk
+    "
+    ^ super compareCaselessWith:aString
+
+    "
+     'aaa' compareCaselessWith:'aaaa' -1
+     'aaaa' compareCaselessWith:'aaa' 1
+     
+     'aaaa' compareCaselessWith:'aaaA' 0
+     'aaaA' compareCaselessWith:'aaaa' 0
+     'aaaAB' compareCaselessWith:'aaaa' 1
+     'aaaaB' compareCaselessWith:'aaaA' 1
+     'aaaa' compareCaselessWith:'aaaAB' -1
+     'aaaA' compareCaselessWith:'aaaaB' -1
+     'aaaa' compareCaselessWith:'aaax'  -1
+     'aaaa' compareCaselessWith:'aaaX'  -1
+    "
+
+    "Created: / 29-05-2019 / 10:48:39 / Claus Gittinger"
+!
+
 compareCollatingWith:aString
     "Compare the receiver with the argument and return 1 if the receiver is
      greater, 0 if equal and -1 if less than the argument in a sorted list.
@@ -1965,6 +2077,8 @@
      'hallo' compareCollatingWith:'hällo'
      'hbllo' compareCollatingWith:'hällo'
     "
+
+    "Modified (format): / 20-06-2018 / 10:14:09 / Claus Gittinger"
 !
 
 compareWith:aString
@@ -2043,6 +2157,62 @@
     ^ super compareWith:aString collating:collatingBoolean
 !
 
+endsWith:aStringOrChar
+    "return true, if the receiver ends with something, aStringOrChar.
+     If aStringOrChar is an empty string, true is returned"
+
+%{  /* NOCONTEXT */
+#ifndef __SCHTEAM__
+    int len1, len2;
+    REGISTER unsigned char *src1, *src2;
+    unsigned char c;
+    REGISTER OBJ slf = self;
+
+    if (__isStringLike(slf)) {
+        if (__isStringLike(aStringOrChar)) {
+            len1 = __qSize(slf);              // includes the 0-byte
+            len2 = __qSize(aStringOrChar);    // includes the 0-byte
+            if (len1 < len2) {
+                RETURN ( false );
+            }
+
+            src1 = __stringVal(slf) + (len1 - len2);
+            src2 = __stringVal(aStringOrChar);
+            while ((c = *src2++) != '\0') {
+                if (c != *src1++) {
+                    RETURN ( false );
+                }
+            }
+            RETURN (true);
+        }
+        if (__isCharacter(aStringOrChar)) {
+            int val;
+
+            val = __intVal(__characterVal(aStringOrChar));
+            if ((unsigned)val <= 0xFF) {
+                len1 = __stringSize(slf);
+                if (len1 > 0) {
+                    RETURN ( (__stringVal(slf)[len1-1] == val) ? true : false);
+                }
+            }
+            RETURN ( false );
+        }
+    }
+#endif /* ! __SCHTEAM__ */
+%}.
+    ^ super endsWith:aStringOrChar
+
+    "
+     'hello world' endsWith:'world'
+     'hello world' endsWith:'earth'
+     'hello world' endsWith:$d
+     'hello world' endsWith:$e
+     '' endsWith:$d
+     'hello world' endsWith:#($r $l $d)
+     'hello world' endsWith:''
+    "
+!
+
 hash
     "return an integer useful as a hash-key.
      This default method uses whichever hash algorithm
@@ -2054,41 +2224,17 @@
     long h = me.hash_fnv1a();
     return __c__._RETURN(STInteger._new(h));
 #else
-    /* Following code is inlined FNV1a hash. 
-     * Inlined for speed (to avoid send).
-     * DO NOT use __symbolHash() here as it 
-     * does not handle characters with codepoint 0
-     * properly - see
-     * https://swing.fit.cvut.cz/projects/stx-jv/ticket/65
-     */
-    REGISTER unsigned int h;
-    REGISTER unsigned char *cp;
-    int l;
-
-    cp = __stringVal(self);
-    l = __stringSize(self);
-    if (__qClass(self) == String) {
-	cont:    
-	h = 2166136261U;
-	while (l >= 4) {
-	    l -= 4;
-	    h = (h ^ cp[0]) * 16777619;
-	    h = (h ^ cp[1]) * 16777619;
-	    h = (h ^ cp[2]) * 16777619;
-	    h = (h ^ cp[3]) * 16777619;
-	    cp += 4;
-    	}
-    	while (l--) {
-	    h = (h ^ *cp++) * 16777619;
-    	}
-    	// make it a smallInteger
-    	h = (h ^ (h >> 30)) & 0x3FFFFFFF;
-    	RETURN ( __mkSmallInteger(h));
-    } else {        
-	int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-	cp += n;
-	goto cont;
+    extern unsigned int __symbolHash(char *);
+    unsigned char *cp = __stringVal(self);
+    unsigned int h;
+
+    if (!__qIsStringLike(self)) {
+	cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
     }
+    h = __symbolHash(cp);
+    // make sure, it fits into a smallInt
+    h = (h ^ (h >> 30)) & 0x3FFFFFFF;
+    RETURN(__mkSmallInteger(h));
 #endif /* not SCHTEAM */
 %}.
     ^ self primitiveFailed
@@ -2164,7 +2310,10 @@
 hash_fnv1a
     "return an integer useful as a hash-key.
      This method uses the fnv-1a algorithm
-     (which is actually a pretty good one)."
+     (which is actually a pretty good one).
+     Notice: this returns a 31bit value,
+	     even on 64bit CPUs, only small 4-byte hashvalues are returned,
+	     (so hash values are independent from the architecture)"
 
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
@@ -2172,34 +2321,31 @@
     long h = me.hash_fnv1a();
     return __c__._RETURN(STInteger._new(h));
 #else
-    REGISTER unsigned int h;
-    REGISTER unsigned char *cp;
-    int l;
-
-    cp = __stringVal(self);
-    l = __stringSize(self);
-    if (__qClass(self) == String) {
-	cont:    
-	h = 2166136261U;
-	while (l >= 4) {
+    REGISTER unsigned int h  = 2166136261u;
+    REGISTER unsigned char *cp = __stringVal(self);
+    INT l  = __stringSize(self);
+
+    if (!__qIsStringLike(self)) {
+	int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+
+	cp += n;
+	l -= n;
+    }
+
+    while (l >= 4) {
 	l -= 4;
 	h = (h ^ cp[0]) * 16777619;
 	h = (h ^ cp[1]) * 16777619;
 	h = (h ^ cp[2]) * 16777619;
 	h = (h ^ cp[3]) * 16777619;
 	cp += 4;
-    	}
-    	while (l--) {
+    }
+    while (l--) {
 	h = (h ^ *cp++) * 16777619;
-    	}
-    	// make it a smallInteger
-    	h = (h ^ (h >> 30)) & 0x3FFFFFFF;
-    	RETURN ( __mkSmallInteger(h));
-    } else {        
-	int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-	cp += n;
-	goto cont;
     }
+    // make it a smallInteger
+    h = (h ^ (h >> 30)) & 0x3FFFFFFF;
+    RETURN ( __mkSmallInteger(h));
 #endif /* not SCHTEAM */
 %}.
     ^ self primitiveFailed
@@ -2207,6 +2353,58 @@
     "
      'a' hash_fnv1a
     "
+
+    "Modified: / 10-02-2019 / 14:05:47 / Claus Gittinger"
+    "Modified (comment): / 09-03-2019 / 20:55:23 / Claus Gittinger"
+!
+
+hash_fnv1a_64
+    "return an integer useful as a hash-key.
+     This method uses the fnv-1a algorithm
+     (which is actually a pretty good one).
+     Notice: this returns 64 bit hashvalues"
+
+%{  /* NOCONTEXT */
+#ifndef __SCHTEAM__
+# ifndef __BORLANDC__
+    unsigned long long h  = 14695981039346656037LLU;
+    unsigned char *cp = __stringVal(self);
+    INT l  = __stringSize(self);
+
+    if (!__qIsStringLike(self)) {
+	int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+
+	cp += n;
+	l -= n;
+    }
+
+    while (l >= 4) {
+	l -= 4;
+	h = (h ^ cp[0]) * 1099511628211LL;
+	h = (h ^ cp[1]) * 1099511628211LL;
+	h = (h ^ cp[2]) * 1099511628211LL;
+	h = (h ^ cp[3]) * 1099511628211LL;
+	cp += 4;
+    }
+    while (l--) {
+	h = (h ^ *cp++) * 1099511628211LL;
+    }
+    // make it a smallInteger
+    h = (h ^ (h >> 30)) & 0x3FFFFFFFFFFFFFFFLL;
+    RETURN ( __mkSmallInteger(h));
+# endif /* not BORLAND */
+#endif /* not SCHTEAM */
+%}.
+    ^ super hash_fnv1a_64
+
+    "
+     '' hash_fnv1a_64
+     'a' hash_fnv1a_64
+     '77kepQFQ8Kl' hash_fnv1a_64
+    "
+
+    "Created: / 09-03-2019 / 08:59:54 / Claus Gittinger"
+    "Modified: / 09-03-2019 / 20:56:40 / Claus Gittinger"
 !
 
 hash_java
@@ -2304,6 +2502,324 @@
     "Created: / 26-12-2011 / 13:53:09 / cg"
 !
 
+levenshteinTo:aString s:substWeight k:kbdTypoWeight c:caseWeight i:insrtWeight d:deleteWeight
+    "parametrized levenshtein. arguments are the costs for
+     substitution, case-change, insertion and deletion of a character."
+
+%{  /* STACK: 2000 */
+#ifndef __SCHTEAM__
+    /*
+     * this is very heavy used when correcting errors
+     * (all symbols are searched for best match) - therefore it must be fast
+     */
+
+    unsigned short *data;
+    int l1, l2;
+    REGISTER int sz;
+    unsigned char *s1, *s2;
+    int v1, v2, v3;
+    INT m;
+    REGISTER unsigned short *dp;
+    REGISTER int rowDelta;
+    REGISTER int j;
+    int i;
+    int iW, cW, sW, kW, dW;
+#   define FASTSIZE 30  /* increase STACK if you increase this ... */
+    unsigned short fastData[(FASTSIZE + 1) * (FASTSIZE + 1)];
+    extern void *malloc();
+
+    if (__qIsStringLike(self) && __isStringLike(aString)
+	&& __bothSmallInteger(insrtWeight, caseWeight)
+	&& __bothSmallInteger(substWeight, deleteWeight)
+	&& __isSmallInteger(kbdTypoWeight)
+    ) {
+	iW = __intVal(insrtWeight);
+	cW = __intVal(caseWeight);
+	sW = __intVal(substWeight);
+	kW = __intVal(kbdTypoWeight);
+	dW = __intVal(deleteWeight);
+	s1 = __stringVal(self);
+	s2 = __stringVal(aString);
+	l1 = __stringSize(self);
+	l2 = __stringSize(aString);
+
+	sz = (l1 < l2) ? l2 : l1;
+	rowDelta = sz + 1;
+	if (sz <= FASTSIZE) {
+	    data = fastData;
+	} else {
+	    /* add ifdef ALLOCA here ... */
+	    data = (unsigned short *)malloc(rowDelta * rowDelta * sizeof(short));
+	    if (! data) goto mallocFailed;
+	}
+
+	data[0] = 0;
+	for (j=1, dp=data+1; j<=sz; j++, dp++)
+	    *dp = dp[-1] + iW;
+
+	for (i=1, dp=data+rowDelta; i<=sz; i++, dp+=rowDelta)
+	    *dp = dp[-rowDelta] + dW;
+
+	for (i=0; i<l1; i++) {
+	    for (j=0; j<l2; j++) {
+		if (s1[i] == s2[j])
+		    m = 0;
+		else if (tolower(s1[i]) == tolower(s2[j]))
+		    m = cW;
+		else if (sW != kW && nextOnKeyboard(tolower(s1[i]), tolower(s2[j])))
+		    m = kW;
+		else
+		    m = sW;
+
+		dp = data + ((i+1)*rowDelta) + j;
+		v2 = dp[0] + iW;
+		v1 = dp[-rowDelta] + m;
+		v3 = dp[-rowDelta+1] + dW;
+		if (v1 < v2) {
+		    if (v1 < v3)
+			m = v1;
+		    else
+			m = v3;
+		} else {
+		    if (v2 < v3)
+			m = v2;
+		    else
+			m = v3;
+		}
+		dp[1] = m;
+	    }
+	}
+	m = data[l1*rowDelta + l2];
+	if (sz > FASTSIZE)
+	    free(data);
+	RETURN ( __mkSmallInteger(m) );
+    }
+mallocFailed: ;
+#endif /* ! __SCHTEAM__ */
+%}.
+
+    ^ super levenshteinTo:aString
+			s:substWeight k:kbdTypoWeight c:caseWeight
+			i:insrtWeight d:deleteWeight
+
+    "
+     'ocmprt' levenshteinTo:'computer'
+     'computer' levenshteinTo:'computer'
+     'ocmputer' levenshteinTo:'computer'
+     'cmputer' levenshteinTo:'computer'
+     'computer' levenshteinTo:'cmputer'
+     'computer' levenshteinTo:'vomputer'
+     'computer' levenshteinTo:'bomputer'
+     'Computer' levenshteinTo:'computer'
+    "
+!
+
+sameAs:aString
+    "Compare the receiver with the argument like =, but ignore case differences.
+     Return true or false."
+
+%{  /* NOCONTEXT */
+    OBJ slf = self;
+    OBJ arg = aString;
+
+    if (__qIsStringLike(slf) &&__isStringLike(arg)) {
+        unsigned char *src1, *src2;
+        int len;
+
+        len = __stringSize(slf);
+        if (len != __stringSize(arg)) {
+            RETURN ( false );
+        }
+
+        src1 = __stringVal(slf);
+        src2 = __stringVal(arg);
+
+        // fast skip over same chars
+        while (len >= sizeof(int)) {
+            if ( ((int*)src1)[0] != ((int*)src2)[0] ) break;
+            len -= sizeof(int);
+            src1 += sizeof(int);
+            src2 += sizeof(int);
+        }
+        while (len > 0) {
+            if ( src1[0] != src2[0] ) break;
+            len--;
+            src1++;
+            src2++;
+        }
+
+        while (len > 0) {
+            // the trouble is, that it is not as easy as we might think on first thought;
+            // for plain ascii (i.e. 7bits), we can check for chars being letters and then ignore the 0x20 bit.
+            // this even works for the national characters except for 0xFF / 0xDF
+            unsigned char ch1 = src1[0];
+            unsigned char ch2 = src2[0];
+
+            if (ch1 != ch2) {
+                unsigned char Uch1 = ch1 & ~0x20; // upper cased
+                unsigned char Uch2 = ch2 & ~0x20; // uppÞer cased
+                if ( (Uch1 >= 'A') && (Uch1 <= 'Z') ) {
+                    // letter
+                    if (Uch1 != Uch2) {
+                        RETURN(false);
+                    }
+                } else {
+                    if ( (Uch1 >= 0xC0) && (Uch1 <= 0xDE) ) {
+                        // national letter
+                        if (Uch1 != Uch2) {
+                            RETURN(false);
+                        }
+                    } else {
+                        // other
+                        RETURN(false);
+                    }
+                }
+            }
+            len--;
+            src1++;
+            src2++;
+        }
+        RETURN (true);
+    }
+%}.
+    "use fallback for wide strings"
+    ^ super sameAs:aString
+
+    "
+     'hello' sameAs:'hello'
+     'hello' sameAs:'Hello'
+     'hello' sameAs:''
+     '' sameAs:'Hello'
+     'hello' sameAs:'hellO'
+     'hello' sameAs:'Hellx'
+     'hällo' sameAs:'HÄllo'  
+     'hÿllo' sameAs:'HŸllo'   // special!!
+    "
+
+    "Created: / 19-07-2018 / 10:44:07 / Claus Gittinger"
+!
+
+startsWith:aStringOrChar
+    "return true, if the receiver starts with something, aStringOrChar.
+     If the argument is empty, true is returned.
+     Notice, that this is similar to, but slightly different from VW's and Squeak's beginsWith:,
+     which are both inconsistent w.r.t. an empty argument."
+
+%{  /* NOCONTEXT */
+#ifdef __SCHTEAM__
+    if (self.isSTString()) {
+	if (aStringOrChar.isSTString()) {
+	    java.lang.String me = self.asString();
+	    java.lang.String other = aStringOrChar.asString();
+	    return __c__._RETURN( me.startsWith(other) ? STObject.True : STObject.False);
+	}
+	if (aStringOrChar.isSTCharacter()) {
+	    char[] me = self.asSTString().characters;
+	    char ch = aStringOrChar.charValue();
+	    return __c__._RETURN( ((me.length > 0)
+				  && (me[0] == ch)) ? STObject.True : STObject.False);
+	}
+    }
+#else
+    int len1, len2;
+    REGISTER unsigned char *src1, *src2;
+    unsigned char c;
+    REGISTER OBJ slf = self;
+
+    if (__qIsStringLike(slf) &&__isStringLike(aStringOrChar)) {
+	src1 = __stringVal(slf);
+	src2 = __stringVal(aStringOrChar);
+
+	if (src1[0] != src2[0]) {
+	    if (__qSize(aStringOrChar) == (OHDR_SIZE+1) /* 1 for the 0-byte */) {
+		RETURN (true);
+	    }
+	    RETURN ( false );
+	}
+
+	len1 = __qSize(slf);
+	len2 = __qSize(aStringOrChar);
+	if (len1 < len2) {
+	    RETURN ( false );
+	}
+
+# ifdef UINT64
+	while (len2 > (OHDR_SIZE+sizeof(UINT64))) {
+	    if ( ((UINT64 *)src1)[0] != ((UINT64 *)src2)[0] ) {
+		RETURN (false);
+	    }
+	    len2 -= sizeof(UINT64);
+	    src1 += sizeof(UINT64);
+	    src2 += sizeof(UINT64);
+	}
+# else
+#  ifdef __UNROLL_LOOPS__
+	while (len2 > (OHDR_SIZE+sizeof(INT)*4)) {
+	    if ( ((unsigned INT *)src1)[0] != ((unsigned INT *)src2)[0]) {
+		RETURN (false);
+	    }
+	    if ( ((unsigned INT *)src1)[1] != ((unsigned INT *)src2)[1]) {
+		RETURN (false);
+	    }
+	    if ( ((unsigned INT *)src1)[2] != ((unsigned INT *)src2)[2]) {
+		RETURN (false);
+	    }
+	    if ( ((unsigned INT *)src1)[3] != ((unsigned INT *)src2)[3]) {
+		RETURN (false);
+	    }
+	    len2 -= sizeof(INT)*4;
+	    src1 += sizeof(INT)*4;
+	    src2 += sizeof(INT)*4;
+	}
+#  endif /* __UNROLL_LOOPS__ */
+# endif /* UINT64 */
+
+	while (len2 > (OHDR_SIZE+sizeof(INT))) {
+	    if ( ((unsigned INT *)src1)[0] != ((unsigned INT *)src2)[0]) {
+		RETURN (false);
+	    }
+	    len2 -= sizeof(INT);
+	    src1 += sizeof(INT);
+	    src2 += sizeof(INT);
+	}
+
+	while ((c = *src2++) != '\0') {
+	    if (c != *src1) {
+		RETURN ( false );
+	    }
+	    src1++;
+	}
+	RETURN (true);
+    }
+    if (__isCharacter(aStringOrChar)) {
+	int val;
+
+	val = __intVal(__characterVal(aStringOrChar));
+	if ((unsigned)val <= 0xFF) {
+	    len1 = __stringSize(slf);
+	    if (len1 > 0) {
+		RETURN ( (__stringVal(slf)[0] == val) ? true : false);
+	    }
+	}
+	RETURN ( false );
+    }
+#endif /* not __SCHTEAM__ */
+%}.
+    ^ super startsWith:aStringOrChar
+
+    "
+     'hello world' startsWith:'hello'
+     'hello world' startsWith:'hella'
+     'hello world' startsWith:'hi'
+     'hello world' startsWith:$h
+     'hello world' startsWith:$H
+     'hello world' startsWith:(Character value:16rFF00)
+     'hello world' startsWith:60
+     'hello world' startsWith:#($h $e $l)
+     'hello world' startsWith:''
+    "
+!
+
 ~= aString
     "Compare the receiver with the argument and return true if the
      receiver is not equal to the argument. Otherwise return false.
@@ -2498,9 +3014,18 @@
     "Modified: / 30-11-2013 / 11:41:40 / cg"
 !
 
+asImmutableCollection
+    "return a write-protected copy of myself"
+
+    ^ self copy changeClassTo:ImmutableString
+
+    "Created: / 15-03-2019 / 13:50:08 / Stefan Vogel"
+!
+
 asImmutableString
     "return a write-protected copy of myself"
 
+    self isSymbol ifTrue:[^ self].
     ^ self copy changeClassTo:ImmutableString
 !
 
@@ -2573,23 +3098,10 @@
     "
 	'Hello WORLD' asLowercase
 	(String new:300) asLowercase
+	#utf8 asLowercase
     "
-!
-
-asPackageId
-    "given a package-string as receiver, return a packageId object.
-     packageIds hide the details of module/directory handling inside the path.
-     See PackageId for the required format of those strings."
-
-    ^ PackageId from: self
-
-    "
-     'stx:libbasic' asPackageId
-     'stx:goodies/net/ssl' asPackageId
-     'stx:hello' asPackageId
-    "
-
-    "Created: / 18-08-2006 / 12:19:54 / cg"
+
+    "Modified: / 27-02-2017 / 15:54:13 / stefan"
 !
 
 asSingleByteString
@@ -2629,7 +3141,7 @@
 
     /* care for instances of a subclass with instVars */
     cls = __qClass(self);
-    if (cls != String) {
+    if ((cls != String) && (cls != ImmutableString)) {
 	cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
     }
     newSymbol = __MKSYMBOL(cp, (OBJ *)0);
@@ -2646,9 +3158,10 @@
 !
 
 asSymbolIfInterned
-    "If a symbol with the receiver's characters is already known, return it. Otherwise, return nil.
+    "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."
 
@@ -2661,10 +3174,10 @@
     OBJ cls = __qClass(self);
     int indx;
 
-    if (cls != String && cls != ImmutableString) {
-	indx = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+    if ((cls != String) && (cls != ImmutableString)) {
+        indx = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
     } else {
-	indx = 0;
+        indx = 0;
     }
     RETURN ( __SYMBOL_OR_NIL(__stringVal(self) + indx));
 #endif /* not __SCHTEAM__ */
@@ -2683,6 +3196,15 @@
     self changeClassTo:ImmutableString
 !
 
+utf16Encoded
+    "UTF-16 encoding is the same as UCS-2 (Unicode16String)"
+
+    ^ self asUnicode16String
+
+    "Created: / 28-05-2019 / 13:01:17 / Stefan Vogel"
+    "Modified (comment): / 28-05-2019 / 14:33:48 / Stefan Vogel"
+!
+
 withTabsExpanded:numSpaces
     "return a string with the characters of the receiver where all tabulator characters
      are expanded into spaces (assuming numSpaces-col tabs).
@@ -2818,10 +3340,10 @@
      */
     if (__qIsStringLike(self)) {
 	char *cp1 = (char *) __stringVal(self);
-	INT l1 = __stringSize(self);
-	INT l2;
+	int l1 = __stringSize(self);
+	int l2;
 	char *cp2 = 0;
-	INT sz;
+	int sz;
 	OBJ newString;
 	char character;
 
@@ -2837,9 +3359,6 @@
 	} else
 	    goto out;
 
-	/* 
-	 * FIXME: check for overflow!!! 
-	 */
 	sz = OHDR_SIZE + l1 + l2 + 1;
 	__qNew(newString, sz);      /* OBJECT ALLOCATION */
 
@@ -2862,7 +3381,7 @@
 	     * by 10% on a P5/200.
 	     */
 	    {
-		INT nw = l1 >> 2;
+		int nw = l1 >> 2;
 
 		if (l1 & 3) nw++;
 		bcopy4(cp1, dstp, nw);
@@ -2882,7 +3401,7 @@
 
 # ifdef bcopy4
 	    if (((INT)dstp & 3) == 0) {
-		INT nw = l2 >> 2;
+		int nw = l2 >> 2;
 
 		if (l2 & 3) nw++;
 		bcopy4(cp2, dstp, nw);
@@ -3180,6 +3699,84 @@
     "
 !
 
+copyReplaceAll:originalChar with:replacementChar ifNone:ersatzValue
+    "return a new string where all originalChar characters
+     are replaced by replacementChars. If no such character is
+     contained in the receiver, then return the value from ersatzValue
+     (can be a block).
+     Reimplemented here for more speed"
+
+%{  /* NOCONTEXT */
+    int count;
+    int sz;
+    REGISTER unsigned char *dstp;
+    OBJ cls, newString;
+
+#ifndef NO_PRIM_STRING
+    if (__isCharacter(originalChar)
+     && __isCharacter(replacementChar)
+     && __isString(ersatzValue)
+     && __qIsStringLike(self)) {
+        unsigned int cVal = __intVal(__characterVal(originalChar));
+        unsigned int newVal;
+        unsigned char* srcp = __stringVal(self);
+
+        if (cVal <= 0xFF) {
+            // first walk along without allocating a new string,
+            // to see if a copy is needed...
+            int count = __stringSize(self);
+            int sz = OHDR_SIZE + count + 1;
+            int i;
+            OBJ newString;
+            unsigned char* dstp;
+
+            for (i=0; i<count; i++) {
+                if (srcp[i] == cVal) goto found;
+            }
+            // not found; return ersatz
+            RETURN( ersatzValue );
+
+        found:
+            // a difference was found at index i
+
+            __PROTECT_CONTEXT__
+            __qNew(newString, sz);  /* OBJECT ALLOCATION */
+            __UNPROTECT_CONTEXT__
+
+            if (newString == NULL) {
+                // allocation failure
+                goto getOutOfHere;
+            }
+            __InstPtr(newString)->o_class = String;
+            __qSTORE(newString, String);
+
+            dstp = __stringVal(newString);
+            memcpy(dstp, srcp, i);
+
+            // continue to the end
+            newVal = __intVal(__characterVal(replacementChar));
+            for (; i<count; i++) {
+                unsigned int ch = srcp[i]; 
+                if (ch == cVal) ch = newVal;
+                dstp[i] = ch;    
+            }
+            dstp[i] = '\0';    
+            RETURN (newString );
+        }
+    }
+  getOutOfHere: ;
+#endif
+%}.
+    ^ super copyReplaceAll:originalChar with:replacementChar ifNone:ersatzValue
+
+    "
+     '12345637' xcopyReplaceAll:$3 with:$* ifNone:'abc'     
+     '12345617' xcopyReplaceAll:$1 with:$* ifNone:'abc'     
+     '12345617' xcopyReplaceAll:$7 with:$* ifNone:'abc'     
+     '12345637' xcopyReplaceAll:$9 with:$* ifNone:'12345637' 
+    "
+!
+
 copyWith:aCharacter
     "return a new string containing the receiver's characters
      and the single new character, aCharacter.
@@ -3406,6 +4003,148 @@
     "
 !
 
+from:start to:stop put:aCharacter
+    "fill part of the receiver with aCharacter.
+     - reimplemented here for speed"
+
+%{  /* NOCONTEXT */
+
+    REGISTER unsigned char *dstp;
+    REGISTER int count, byteValue;
+    int len, index1, index2;
+    OBJ cls;
+    
+    // fprintf(stderr, "fill...\n");
+    if (__isCharacter(aCharacter)
+     && __bothSmallInteger(start, stop)) {
+        len = __stringSize(self);
+        index1 = __intVal(start);
+        index2 = __intVal(stop);
+
+        dstp = __stringVal(self) + index1 - 1;
+        if ((cls = __qClass(self)) != @global(String)) {
+            int nInst;
+
+            nInst = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+            dstp += nInst;
+            len -= nInst;
+        }
+
+        byteValue = __intVal(__characterVal(aCharacter));
+        if (((unsigned)byteValue <= 0xFF)
+         && (index1 <= index2)
+         && (index1 > 0)) {
+            if (index2 <= len) {
+                count = index2 - index1 + 1;
+
+#ifdef memset4
+                if (count > 20) {
+                    /* fill unaligned part */
+                    while (((unsigned INT)dstp & 3) != 0) {
+                        *dstp++ = byteValue;
+                        count--;
+                    }
+                    /* fill aligned part */
+                    {
+                        int n4 = count & ~3;
+                        int v4, nW;
+
+                        v4 = (byteValue << 8) | byteValue;
+                        v4 = (v4 << 16) | v4;
+                        nW = n4>>2;
+                        memset4(dstp, v4, nW);
+                        count -= n4;
+                        dstp += n4;
+                    }
+                    while (count--) {
+                        *dstp++ = byteValue;
+                    }
+                    RETURN (self);
+                }
+#endif /* memset4 */
+
+#if (__POINTER_SIZE__ == 8)
+                {
+                    INT v8;
+
+                    v8 = (byteValue << 8) | byteValue;
+                    v8 = (v8 << 16) | v8;
+                    v8 = (v8 << 32) | v8;
+
+                    /* fill unaligned part */
+                    while ((count > 0) && (((unsigned INT)dstp & 3) != 0)) {
+                        *dstp++ = byteValue;
+                        count--;
+                    }
+
+                    if ((count >= 4) && (((unsigned INT)dstp & 7) != 0)) {
+                        ((unsigned int *)dstp)[0] = v8;
+                        dstp += 4;
+                        count -= 4;
+                    }
+
+                    /* fill aligned part */
+                    while (count >= 8) {
+                        ((unsigned INT *)dstp)[0] = v8;
+                        dstp += 8;
+                        count -= 8;
+                    }
+
+                    /* fill rest */
+                    if (count >= 4) {
+                        ((unsigned int *)dstp)[0] = v8;
+                        dstp += 4;
+                        count -= 4;
+                    }
+                    if (count >= 2) {
+                        ((unsigned short *)dstp)[0] = v8;
+                        dstp += 2;
+                        count -= 2;
+                    }
+                    if (count) {
+                        *dstp = byteValue;
+                    }
+                    RETURN (self);
+                }
+#endif /* 64bit */
+
+#ifdef FAST_MEMSET
+                memset(dstp, byteValue, count);
+#else
+# ifdef __UNROLL_LOOPS__
+                while (count >= 8) {
+                    dstp[0] = dstp[1] = dstp[2] = dstp[3] =
+                    dstp[4] = dstp[5] = dstp[6] = dstp[7] = byteValue;
+                    dstp += 8;
+                    count -= 8;
+                }
+# endif /* __UNROLL_LOOPS__ */
+                while (count--) {
+                    *dstp++ = byteValue;
+                }
+#endif
+                RETURN (self);
+            }
+        }
+    }
+%}.
+    "
+     fall back in case of non-integer index or out-of-bound index/value;
+     will eventually lead to an out-of-bound signal raise
+    "
+    ^ super from:start to:stop put:aCharacter
+
+    "
+     (String new:10) from:1 to:10 put:$a
+     (String new:20) from:10 to:20 put:$b
+     (String new:20) from:1 to:10 put:$c
+     (String new:20) from:1 to:10 put:$c 
+     (String new:100) from:2 to:99 put:$c 
+    "
+
+    "Created: / 26-03-2019 / 11:11:56 / Claus Gittinger"
+!
+
 replaceAll:oldCharacter with:newCharacter
     "replace all oldCharacters by newCharacter in the receiver.
 
@@ -3579,51 +4318,51 @@
     REGISTER unsigned char *ep0;
 
     /* ignore instances of subclasses ... */
-    if (__qClass(self) == String) {
-	cp = cp0 = __stringVal(self);
-
-	/*
-	 * find first non-whiteSpace from beginning
-	 */
+    if (__isStringLike(self)) {
+        cp = cp0 = __stringVal(self);
+
+        /*
+         * find first non-whiteSpace from beginning
+         */
 #ifdef UINT64
-	while (*((UINT64 *)cp) == 0x2020202020202020L) {
-	    cp += 8;
-	}
+        while (*((UINT64 *)cp) == 0x2020202020202020L) {
+            cp += 8;
+        }
 #endif
-	while (*((unsigned *)cp) == 0x20202020) {
-	    cp += 4;
-	}
-	while ((c = *cp)
-	 && (c <= ' ')
-	 && ((c == ' ') || (c == '\n') || (c == '\t')
-			|| (c == '\r') || (c == '\f'))
-	) {
-	    cp++;
-	}
-
-	/*
-	 * find first non-whiteSpace from end
-	 */
-	ep = ep0 = cp0 + __stringSize(self) - 1;
-	while ((ep >= cp) && (*ep == ' ')) ep--;
-	c = *ep;
-	while ((ep >= cp) &&
-	       (c <= ' ') &&
-	       ((c == ' ') || (c == '\n') || (c == '\t')
-			   || (c == '\r') || (c == '\f'))) {
-	    ep--;
-	    c = *ep;
-	}
-
-	/*
-	 * no whiteSpace ?
-	 */
-	if ((cp == cp0) && (ep == ep0)) {
-	    RETURN(self);
-	}
-
-	startIndex = __mkSmallInteger(cp - cp0 + 1);
-	endIndex = __mkSmallInteger(ep - cp0 + 1);
+        while (*((unsigned *)cp) == 0x20202020) {
+            cp += 4;
+        }
+        while ((c = *cp)
+         && (c <= ' ')
+         && ((c == ' ') || (c == '\n') || (c == '\t')
+                        || (c == '\r') || (c == '\f'))
+        ) {
+            cp++;
+        }
+
+        /*
+         * find first non-whiteSpace from end
+         */
+        ep = ep0 = cp0 + __stringSize(self) - 1;
+        while ((ep >= cp) && (*ep == ' ')) ep--;
+        c = *ep;
+        while ((ep >= cp) &&
+               (c <= ' ') &&
+               ((c == ' ') || (c == '\n') || (c == '\t')
+                           || (c == '\r') || (c == '\f'))) {
+            ep--;
+            c = *ep;
+        }
+
+        /*
+         * no whiteSpace ?
+         */
+        if ((cp == cp0) && (ep == ep0)) {
+            RETURN(self);
+        }
+
+        startIndex = __mkSmallInteger(cp - cp0 + 1);
+        endIndex = __mkSmallInteger(ep - cp0 + 1);
     }
 %}.
     startIndex == 0 ifTrue:[^ super withoutSeparators].
@@ -3640,6 +4379,8 @@
      '    hello    ' withoutSeparators
      '        ' withoutSeparators
     "
+
+    "Modified: / 12-12-2019 / 14:16:51 / Stefan Vogel"
 !
 
 withoutSpaces
@@ -3660,37 +4401,37 @@
     unsigned char *ep0;
 
     /* ignore instances of subclasses ... */
-    if (__qClass(self) == String) {
-	cp = cp0 = __stringVal(self);
-
-	/*
-	 * find first non-blank from beginning
-	 */
+    if (__isStringLike(self)) {
+        cp = cp0 = __stringVal(self);
+
+        /*
+         * find first non-blank from beginning
+         */
 #ifdef UINT64
-	while (*((UINT64 *)cp) == 0x2020202020202020L) {
-	    cp += 8;
-	}
+        while (*((UINT64 *)cp) == 0x2020202020202020L) {
+            cp += 8;
+        }
 #endif /* UINT64 */
-	while (*((unsigned *)cp) == 0x20202020) {
-	    cp += 4;
-	}
-	while (*cp == ' ') cp++;
-
-	/*
-	 * find first non-blank from end
-	 */
-	ep = ep0 = cp0 + __stringSize(self) - 1;
-	while ((ep >= cp) && (*ep == ' ')) ep--;
-
-	/*
-	 * no blanks ?
-	 */
-	if ((cp == cp0) && (ep == ep0)) {
-	    RETURN(self);
-	}
-
-	startIndex = __mkSmallInteger(cp - cp0 + 1);
-	endIndex = __mkSmallInteger(ep - cp0 + 1);
+        while (*((unsigned *)cp) == 0x20202020) {
+            cp += 4;
+        }
+        while (*cp == ' ') cp++;
+
+        /*
+         * find first non-blank from end
+         */
+        ep = ep0 = cp0 + __stringSize(self) - 1;
+        while ((ep >= cp) && (*ep == ' ')) ep--;
+
+        /*
+         * no blanks ?
+         */
+        if ((cp == cp0) && (ep == ep0)) {
+            RETURN(self);
+        }
+
+        startIndex = __mkSmallInteger(cp - cp0 + 1);
+        endIndex = __mkSmallInteger(ep - cp0 + 1);
     }
 %}.
     startIndex == 0 ifTrue:[^ super withoutSpaces].
@@ -3707,6 +4448,71 @@
      '    hello    ' withoutSpaces
      '        ' withoutSpaces
     "
+
+    "Modified: / 12-12-2019 / 14:16:58 / Stefan Vogel"
+!
+
+withoutTrailingSeparators
+    "return a copy of myself without trailing separators.
+     Notice: this does remove tabs, newline or any other whitespace.
+     Returns an empty string, if the receiver consist only of whitespace."
+
+    |endIndex   "{ Class: SmallInteger }"|
+
+    endIndex := -1.
+%{
+    REGISTER unsigned char *cp0;
+    REGISTER unsigned char *ep;
+    REGISTER unsigned char c;
+    REGISTER unsigned char *ep0;
+
+    /* ignore instances of subclasses ... */
+    if (__isStringLike(self)) {
+        cp0 = __stringVal(self);
+
+        /*
+         * find first non-whiteSpace from end
+         */
+        ep = ep0 = cp0 + __stringSize(self) - 1;
+        while ((ep >= cp0) && (*ep == ' ')) ep--;
+        c = *ep;
+        while ((ep >= cp0) &&
+               (c <= ' ') &&
+               ((c == ' ') || (c == '\n') || (c == '\t')
+                           || (c == '\r') || (c == '\f'))) {
+            ep--;
+            c = *ep;
+        }
+
+        /*
+         * no whiteSpace ?
+         */
+        if (ep == ep0) {
+            RETURN(self);
+        }
+
+        endIndex = __mkSmallInteger(ep - cp0 + 1);
+    }
+%}.
+    endIndex == -1 ifTrue:[^ super withoutTrailingSeparators].
+    endIndex == 0 ifTrue:[^ ''].
+    ^ self copyFrom:1 to:endIndex
+
+
+    "
+     '    foo    ' withoutTrailingSeparators
+     'foo    '     withoutTrailingSeparators
+     '    foo'     withoutTrailingSeparators
+     '       '     withoutTrailingSeparators
+     'foo'         withoutTrailingSeparators
+     'f'           withoutTrailingSeparators
+     'f '          withoutTrailingSeparators
+     ''            withoutTrailingSeparators
+     ('  ' , Character tab , ' foo   ') withoutTrailingSeparators inspect
+     ('   foo' , Character tab) withoutTrailingSeparators inspect
+    "
+
+    "Created: / 12-12-2019 / 14:00:23 / Stefan Vogel"
 ! !
 
 !String methodsFor:'printing & storing'!
@@ -3721,14 +4527,14 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     if (self.isStringLike()) {
-        org.exept.stj.STSystem.err.print(self.asString());
-        return context._RETURN(self);
+	org.exept.stj.STSystem.err.print(self.asString());
+	return context._RETURN(self);
     }
 #else
     if (__qIsStringLike(self)) {
-        console_fprintf(stderr, "%s" , __stringVal(self));
-        console_fflush(stderr);
-        RETURN (self);
+	console_fprintf(stderr, "%s" , __stringVal(self));
+	console_fflush(stderr);
+	RETURN (self);
     }
 #endif /* not SCHTEAM */
 %}.
@@ -3744,14 +4550,14 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     if (self.isStringLike()) {
-        org.exept.stj.STSystem.err.println(self.asString());
-        return context._RETURN(self);
+	org.exept.stj.STSystem.err.println(self.asString());
+	return context._RETURN(self);
     }
 #else
     if (__qIsStringLike(self)) {
-        console_fprintf(stderr, "%s\n" , __stringVal(self));
-        console_fflush(stderr);
-        RETURN (self);
+	console_fprintf(stderr, "%s\n" , __stringVal(self));
+	console_fflush(stderr);
+	RETURN (self);
     }
 #endif
 %}.
@@ -3770,9 +4576,9 @@
     return context._RETURN(self);
 #else
     if (__qIsStringLike(self)) {
-        console_fprintf(stdout, "%s" , __stringVal(self));
-        console_fflush(stdout);
-        RETURN (self);
+	console_fprintf(stdout, "%s" , __stringVal(self));
+	console_fflush(stdout);
+	RETURN (self);
     }
 #endif
 %}.
@@ -3791,36 +4597,25 @@
     return context._RETURN(self);
 #else
     if (__qIsStringLike(self)) {
-        console_fprintf(stdout, "%s\n" , __stringVal(self));
-        console_fflush(stdout);
-        RETURN (self);
+	console_fprintf(stdout, "%s\n" , __stringVal(self));
+	console_fflush(stdout);
+	RETURN (self);
     }
 #endif
 %}.
 !
 
-displayString
-    "return a string used when displaying the receiver in a view."
-
-    ^ super displayString.
-"/    ^ self storeString.
-
-    "
-     'hello' -> 'hello'
-    "
-!
-
 errorPrint
     "print the receiver on standard error, if the global Stderr is nil;
      otherwise, fall back to the inherited errorPrint, which sends the string to
      the Stderr stream or to a logger.
-     Redefined to be able to print during early startup, 
+     Redefined to be able to print during early startup,
      when the stream classes have not yet been initialized (i.e. Stderr is nil)."
 
     Stderr isNil ifTrue:[
-        self _errorPrint
+	self _errorPrint
     ] ifFalse:[
-        super errorPrint
+	super errorPrint
     ].
 
     "
@@ -3835,13 +4630,13 @@
     "print the receiver on standard error, followed by a cr,
      if the global Stderr is nil; otherwise, fall back to the inherited errorPrintCR,
      which sends the string to the Stderr stream or to a logger.
-     Redefined to be able to print during early startup, 
+     Redefined to be able to print during early startup,
      when the stream classes have not yet been initialized (i.e. Stderr is nil)."
 
     Stderr isNil ifTrue:[
-        self _errorPrintCR
+	self _errorPrintCR
     ] ifFalse:[
-        super errorPrintCR
+	super errorPrintCR
     ].
 !
 
@@ -3855,14 +4650,14 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     if (self.isStringLike()) {
-        org.exept.stj.STSystem.err.print(self.asString());
-        return context._RETURN(self);
+	org.exept.stj.STSystem.err.print(self.asString());
+	return context._RETURN(self);
     }
 #else
     if (__qIsStringLike(self)) {
-        console_fprintf(stderr, "%s" , __stringVal(self));
-        console_fflush(stderr);
-        RETURN (self);
+	console_fprintf(stderr, "%s" , __stringVal(self));
+	console_fflush(stderr);
+	RETURN (self);
     }
 #endif /* not SCHTEAM */
 %}.
@@ -3885,14 +4680,14 @@
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
     if (self.isStringLike()) {
-        org.exept.stj.STSystem.err.println(self.asString());
-        return context._RETURN(self);
+	org.exept.stj.STSystem.err.println(self.asString());
+	return context._RETURN(self);
     }
 #else
     if (__qIsStringLike(self)) {
-        console_fprintf(stderr, "%s\n" , __stringVal(self));
-        console_fflush(stderr);
-        RETURN (self);
+	console_fprintf(stderr, "%s\n" , __stringVal(self));
+	console_fflush(stderr);
+	RETURN (self);
     }
 #endif
 %}.
@@ -3911,9 +4706,9 @@
     return context._RETURN(self);
 #else
     if (__qIsStringLike(self)) {
-        console_fprintf(stdout, "%s" , __stringVal(self));
-        console_fflush(stdout);
-        RETURN (self);
+	console_fprintf(stdout, "%s" , __stringVal(self));
+	console_fflush(stdout);
+	RETURN (self);
     }
 #endif
 %}.
@@ -3932,9 +4727,9 @@
     return context._RETURN(self);
 #else
     if (__qIsStringLike(self)) {
-        console_fprintf(stdout, "%s\n" , __stringVal(self));
-        console_fflush(stdout);
-        RETURN (self);
+	console_fprintf(stdout, "%s\n" , __stringVal(self));
+	console_fflush(stdout);
+	RETURN (self);
     }
 #endif
 %}.
@@ -3944,13 +4739,13 @@
     "print the receiver on standard output, if the global Stdout is nil;
      otherwise, fall back to the inherited print,
      which sends the string to the Stdout stream.
-     Redefined to be able to print during early startup, 
+     Redefined to be able to print during early startup,
      when the stream classes have not yet been initialized (i.e. Stdout is nil)."
 
     Stdout isNil ifTrue:[
-        self _print
+	self _print
     ] ifFalse:[
-        super print
+	super print
     ].
 !
 
@@ -3958,28 +4753,33 @@
     "print the receiver on standard output, followed by a cr,
      if the global Stdout is nil; otherwise, fall back to the inherited errorPrintCR,
      which sends the string to the Stdout stream.
-     Redefined to be able to print during early startup, 
+     Redefined to be able to print during early startup,
      when the stream classes have not yet been initialized (i.e. Stdout is nil)."
 
     Stdout isNil ifTrue:[
-        self _printCR
+	self _printCR
     ] ifFalse:[
-        super printCR
+	super printCR
     ].
 !
 
 printfPrintString:formatString
+    <unsave>
+
     "non-standard but sometimes useful.
      Return a printed representation of the receiver as specified by formatString,
      which is defined by printf.
+
+     If you use this, be aware, that the format string must be correct and something like %s.
+
      This method is NONSTANDARD and may be removed without notice.
-     WARNNG: this goes directly to the C-printf function and may therefore be inherently unsafe.
-     Please use the printf: method, which is both safe 
-     and completely implemented in Smalltalk."
-
-%{  /* STACK: 1000 */
+
+     WARNING: this goes directly to the C-printf function and may therefore be inherently unsafe.
+     Please use the printf: method, which is both safe and completely implemented in Smalltalk."
+
+%{  /* STACK: 32000 */
 #ifndef __SCHTEAM__
-    char buffer[800];
+    char buffer[8192];
     char *buf = buffer;
     int bufsize = sizeof(buffer);
     char *mallocbuf = NULL;
@@ -4041,6 +4841,8 @@
      'hello' printfPrintString:'%%900s -> %900s'
      'hello' printfPrintString:'%%-900s -> %-900s'
     "
+
+    "Modified (comment): / 03-07-2017 / 15:12:58 / cg"
 !
 
 storeOn:aStream
@@ -4048,9 +4850,9 @@
 
     aStream nextPut:$'.
     (self includes:$') ifTrue:[
-        self printWithQuotesDoubledOn:aStream
+	self printWithQuotesDoubledOn:aStream
     ] ifFalse:[
-        aStream nextPutAll:self
+	aStream nextPutAll:self
     ].
     aStream nextPut:$'
 
@@ -4103,6 +4905,15 @@
     ^ 1
 !
 
+bytesPerCharacterNeeded
+    "return the actual underlying string's required bytesPerCharacter
+     (i.e. checks if all characters really need that depth)"
+
+    ^ 1
+
+    "Created: / 25-03-2019 / 16:24:24 / Claus Gittinger"
+!
+
 characterSize
     "answer the size in bits of my largest character (actually only 7 or 8)"
 
@@ -4201,11 +5012,68 @@
 !
 
 containsNon8BitElements
-    "return true, if the underlying string contains elements larger than a single byte"
+    "return true, if the receiver contains elements larger than a single byte.
+     Per definition not."
 
     ^ false.
 !
 
+isBlank
+    "return true, if the receiver's size is 0 or if it contains only spaces.
+     Q: should we care for whiteSpace in general here ?"
+
+%{  /* NOCONTEXT */
+#ifndef __SCHTEAM__
+    REGISTER unsigned char *src;
+    REGISTER unsigned char c;
+    OBJ cls;
+
+    src = __stringVal(self);
+    if ((cls = __qClass(self)) != String)
+	src += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+
+    // hop along in bigger steps if possible
+# ifdef UINT64
+    while (*((UINT64 *)src) == 0x2020202020202020L) {
+	src += 8;
+    }
+# endif /* UINT64 */
+    while (*((unsigned *)src) == 0x20202020) {
+	src += 4;
+    }
+    while (*((unsigned short *)src) == 0x2020) {
+	src += 2;
+    }
+
+    while ((c = *src++) == ' ')
+	;; /* just walking along */
+    if (c != '\0') {
+	RETURN ( false );
+    }
+    RETURN ( true );
+# endif /* ! __SCHTEAM__ */
+%}.
+    ^ super isBlank
+
+    "Modified: / 24-11-2017 / 08:56:17 / cg"
+!
+
+isEmpty
+    "return true if the receiver is empty (i.e. if size == 0)
+     Redefined here for performance"
+
+%{  /* NOCONTEXT */
+#ifndef __SCHTEAM__
+    if (__isStringLike(self)) {
+	RETURN ( (__stringSize(self) == 0) ? true : false);
+    }
+#endif /* ! __SCHTEAM__ */
+%}.
+    ^ self size == 0
+
+    "Modified: / 16-02-2017 / 14:57:50 / stefan"
+!
+
 isWideString
     "true if I require more than one byte per character"
 
@@ -4225,7 +5093,7 @@
     int indx;
 
     cls = __qClass(self);
-    if (cls != String) {
+    if ((cls != String) && (cls != ImmutableString)) {
 	indx = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
     } else {
 	indx = 0;
@@ -4242,6 +5110,22 @@
     "
 !
 
+notEmpty
+    "return true if the receiver is not empty (i.e. if size ~~ 0)
+     Redefined here for performance"
+
+%{  /* NOCONTEXT */
+#ifndef __SCHTEAM__
+    if (__isStringLike(self)) {
+	RETURN ( (__stringSize(self) != 0) ? true : false);
+    }
+#endif /* ! __SCHTEAM__ */
+%}.
+    ^ self size ~~ 0
+
+    "Modified: / 16-02-2017 / 15:00:42 / stefan"
+!
+
 size
     "return the number of characters in myself.
      Reimplemented here to avoid the additional size->basicSize send
@@ -4271,39 +5155,17 @@
 !
 
 utf8DecodedMaxBytes
-    "return the number of charcters needed when this string is
+    <resource: #obsolete>
+    "return the number of characters needed when this string is
      decoded from UTF-8."
 
-%{  /* NOCONTEXT */
-
-    unsigned char *cp = __stringVal(self);
-    unsigned char *last = cp + __stringSize(self);
-    int max = 1;
-
-    if (!__isStringLike(self)) {
-	cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-    }
-
-    for ( ; cp < last; cp++) {
-	unsigned char mask = *cp & 0xF0;
-	if (mask != 0) {
-	    if ((mask & 0xE0 )== 0xC0) {  if (max < 2) max = 2; }
-	    else if (mask == 0xE0) { if (max < 3) max = 3; }
-	    else if (mask == 0xF0) { max = 4; break;}
-	}
-    }
-    RETURN (__mkSmallInteger(max));
-%}.
-
-    "
-     'hello world' utf8DecodedMaxBytes
-     'ä' utf8Encoded utf8DecodedMaxBytes
-     'äΣΔΨӕἤῴ' utf8Encoded utf8DecodedMaxBytes
-    "
+    ^ self utf8DecodedSize.
+
+    "Modified (comment): / 07-02-2017 / 15:10:33 / stefan"
 !
 
 utf8DecodedSize
-    "return the number of charcters needed when this string is
+    "return the number of characters needed when this string is
      decoded from UTF-8."
 
 %{  /* NOCONTEXT */
@@ -4327,11 +5189,13 @@
      'ä' utf8Encoded utf8DecodedSize
      'äΣΔΨӕἤῴ' utf8Encoded utf8DecodedSize
     "
+
+    "Modified: / 07-02-2017 / 15:10:40 / stefan"
 ! !
 
 !String methodsFor:'sorting & reordering'!
 
-reverse
+reverseFrom:startIndex to:endIndex
     "in-place reverse the characters of the string.
      WARNING: this is a destructive operation, which modifies the receiver.
 	      Please use reversed (with a d) for a functional version."
@@ -4343,154 +5207,61 @@
     REGISTER char c;
     REGISTER unsigned char *hip, *lowp;
 
-    if (__isString(self)) {
-	lowp = __stringVal(self);
-	hip = lowp + __stringSize(self) - 1;
-	while (lowp < hip) {
-	    c = *lowp;
-	    *lowp = *hip;
-	    *hip = c;
-	    lowp++;
-	    hip--;
+    if (__isString(self)
+     && __isSmallInteger(startIndex)
+     && __isSmallInteger(endIndex)) {
+	int _start = __intVal(startIndex) - 1;
+	int _end = __intVal(endIndex) - 1;
+
+	if ((_start >= 0)
+	 && (_end < __stringSize(self))
+	 && (_end >= _start)) {
+	    lowp = __stringVal(self) + _start;
+	    hip = __stringVal(self) + _end;
+	    while (lowp < hip) {
+		c = *lowp;
+		*lowp = *hip;
+		*hip = c;
+		lowp++;
+		hip--;
+	    }
+	    RETURN ( self );
 	}
-	RETURN ( self );
     }
-    #endif
+#endif
 %}.
-    ^ super reverse
+    ^ super reverseFrom:startIndex to:endIndex
+
+    "
+     '1234567890' copy reverseFrom:2 to:5
+     '1234567890' copy reverse
+     '1234567890' copy reversed
+
+     |t|
+     t := '1234567890abcdefghijk' copy.
+     t reverseFrom:1 to:10.
+     t reverseFrom:11 to:t size.
+     t reverseFrom:1 to:t size.
+     t
+
+     |t|
+     t := '1234567890abcdefghijk' copy.
+     t reverseFrom:1 to:2.
+     t reverseFrom:3 to:t size.
+     t reverseFrom:1 to:t size.
+     t
+    "
+
+    "Created: / 01-05-2017 / 12:50:18 / cg"
+    "Modified (comment): / 01-05-2017 / 14:05:41 / cg"
 ! !
 
+
 !String methodsFor:'substring searching'!
 
-indexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:caseSensitive
-    "redefined as primitive for maximum speed (BM)"
-
-    |notFound|
-
-%{  /* STACK:4000 */
-#ifndef __SCHTEAM__
-    if (__qIsStringLike(self)
-     && __isStringLike(aSubString)
-     && (caseSensitive == true)
-     && (__isSmallInteger(startIndex))
-     && (__intVal(startIndex) > 0)
-    ) {
-	unsigned char *y = __stringVal(self);
-	unsigned char *x = __stringVal(aSubString);
-	int m = __stringSize(aSubString);
-	int n = __stringSize(self);
-#       define MAX_PATTERN_SIZE 128
-#       define XSIZE 256
-#       define ASIZE 256
-#       define MAX(a,b) (a>b ? a : b)
-
-	if (m == 0) {
-#if 1
-	    /* empty string does not match */
-	    RETURN(__mkSmallInteger(0));
-#else
-	    /* empty string matches */
-	    RETURN(startIndex);
-#endif
-	}
-	if (m <= XSIZE) {
-	    int i, j;
-	    static int lastPatternSize = 0;
-	    static char lastPattern[MAX_PATTERN_SIZE+1] = { 0 };
-	    static int bmGs[XSIZE+1], bmBc[ASIZE];
-
-#           define preBmBc(x, m, bmBc) {          \
-	       int i;                             \
-						  \
-	       for (i = 0; i < ASIZE; ++i)        \
-		  bmBc[i] = m;                    \
-	       for (i = 0; i < m - 1; ++i)        \
-		  bmBc[x[i]] = m - i - 1;         \
-	    }
-
-#           define suffixes(x, m, suff) {                       \
-	       int f, g, i;                                     \
-								\
-	       suff[m - 1] = m;                                 \
-	       g = m - 1;                                       \
-	       for (i = m - 2; i >= 0; --i) {                   \
-		  if (i > g && suff[i + m - 1 - f] < i - g)     \
-		     suff[i] = suff[i + m - 1 - f];             \
-		  else {                                        \
-		     if (i < g)                                 \
-			g = i;                                  \
-		     f = i;                                     \
-		     while (g >= 0 && x[g] == x[g + m - 1 - f]) \
-			--g;                                    \
-		     suff[i] = f - g;                           \
-		  }                                             \
-	       }                                                \
-	    }
-
-#           define preBmGs(x, m, bmGs) {                        \
-	       int i, j, suff[XSIZE];                           \
-								\
-	       suffixes(x, m, suff);                            \
-								\
-	       for (i = 0; i < m; ++i)                          \
-		  bmGs[i] = m;                                  \
-	       j = 0;                                           \
-	       for (i = m - 1; i >= 0; --i)                     \
-		  if (suff[i] == i + 1)                         \
-		     for (; j < m - 1 - i; ++j)                 \
-			if (bmGs[j] == m)                       \
-			   bmGs[j] = m - 1 - i;                 \
-	       for (i = 0; i <= m - 2; ++i)                     \
-		  bmGs[m - 1 - suff[i]] = m - 1 - i;            \
-	    }
-
-	    /* tables only depend on pattern; so we can cache them in case the same string is searched again */
-	    if ((m == lastPatternSize)
-	     && (strcmp(lastPattern, x) == 0)) {
-		/* tables are still valid */
-		// printf("valid: \"%s\"\n", lastPattern);
-	    } else {
-		/* Preprocessing */
-		// printf("compute: \"%s\"\n", lastPattern);
-		preBmGs(x, m, bmGs);
-		preBmBc(x, m, bmBc);
-		if (m <= MAX_PATTERN_SIZE) {
-		    // printf("cache for: \"%s\"\n", lastPattern);
-		    strcpy(lastPattern, x);
-		    lastPatternSize = m;
-		}
-	    }
-
-	    /* Searching */
-	    j = __intVal(startIndex) - 1;
-	    while (j <= n - m) {
-	       for (i = m - 1; i >= 0 && x[i] == y[i + j]; --i);
-	       if (i < 0) {
-		  RETURN (__mkSmallInteger(j+1));
-		  j += bmGs[0];
-	       } else {
-		  int s1 = bmGs[i];
-		  int s2 = bmBc[y[i + j]] - m + 1 + i;
-		  j += MAX(s1, s2);
-	       }
-	    }
-	    notFound = true;
-	}
-    }
-#endif /* ! __SCHTEAM__ */
-%}.
-    notFound == true ifTrue:[
-	^ exceptionValue value.
-    ].
-    ^ self slowIndexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:caseSensitive
-
-    "Modified: / 05-08-2012 / 12:27:31 / cg"
-!
-
-slowIndexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:caseSensitive
+caseInsensitiveIndexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue
     "naive search fallback (non-BM).
-     Use this for short searchStrings (<= 2)
-     or for caseInSensitive searches"
+     Private method to speed up caseInSensitive searches"
 
     |notFound|
 
@@ -4508,9 +5279,7 @@
 	int c_lenSubstring = __stringSize(aSubString);
 	int c_idx0Max = c_lenSelf - c_lenSubstring;
 	unsigned char c_first;
-	unsigned char c_ucFirst;
-	unsigned char c_lcFirst;
-	unsigned char c_oppositeCaseFirst;
+	unsigned char c_oppositeCaseFirst = 0;
 	int i;
 
 	if (c_lenSubstring == 0) {
@@ -4530,16 +5299,14 @@
 	    goto getOutOfHere;
 	}
 
-	c_first = c_lcFirst = c_substring[0];
+	c_first = c_substring[0];
 	if (((c_first >= 'A') && (c_first <= 'Z'))
-	 || ((c_first >= 0xC0) && (c_first <= 0xDE))) {
-	    c_ucFirst = c_first;
-	    c_lcFirst = c_oppositeCaseFirst = c_first - 'A' + 'a';
+	 || ((c_first >= 0xC0) && (c_first <= 0xDE) && (c_first != 0xD7))) {
+	    c_oppositeCaseFirst = c_first - 'A' + 'a';
 	} else {
 	    if (((c_first >= 'a') && (c_first <= 'z'))
-	     || ((c_first >= 0xE0) && (c_first <= 0xFE))) {
-		c_lcFirst = c_first;
-		c_ucFirst = c_oppositeCaseFirst = c_first - 'a' + 'A';
+	      || ((c_first >= 0xE0) && (c_first <= 0xFE) && (c_first != 0xF7))) {
+		c_oppositeCaseFirst = c_first - 'a' + 'A';
 	    }
 	}
 
@@ -4560,34 +5327,27 @@
 
 	    // find the first char
 	    c_selfChar = c_pSelfI[0];
-	    if (c_selfChar != c_first) {
-		if (caseSensitive == true) continue;
-		if (c_selfChar != c_oppositeCaseFirst) {
+	    if (c_selfChar != c_first && c_selfChar != c_oppositeCaseFirst) {
 searchNext: ;
-		    continue;
-		}
+		continue;
 	    }
 
 	    // first char matches
 	    // compare rest
 	    for (j=1; j<c_lenSubstring; j++) {
-		unsigned char c_selfChar, c_subChar, c_lcSubChar, c_ucSubChar;
-
-		c_subChar = c_substring[j];
-		c_selfChar = c_pSelfI[j];
+		unsigned char c_subChar = c_substring[j];
+		unsigned char c_selfChar = c_pSelfI[j];
 
 		if (c_selfChar == c_subChar) continue;
-		if (caseSensitive == true) goto searchNext;
-
-		c_lcSubChar = c_subChar;
-		if (((c_lcSubChar >= 'A') && (c_lcSubChar <= 'Z'))
-		 || ((c_lcSubChar >= 0xC0) && (c_lcSubChar <= 0xDE))) {
-		    c_lcSubChar = c_subChar - 'A' + 'a';
+
+		if (((c_subChar >= 'A') && (c_subChar <= 'Z'))
+		 || ((c_subChar >= 0xC0) && (c_subChar <= 0xDE) && (c_subChar != 0xD7))) {
+		    unsigned char c_lcSubChar = c_subChar - 'A' + 'a';
 		    if (c_selfChar != c_lcSubChar) goto searchNext;
 		} else {
-		    if (((c_lcSubChar >= 'a') && (c_lcSubChar <= 'z'))
-		     || ((c_lcSubChar >= 0xE0) && (c_lcSubChar <= 0xFE))) {
-			c_ucSubChar = c_subChar - 'a' + 'A';
+		    if (((c_subChar >= 'a') && (c_subChar <= 'z'))
+		     || ((c_subChar >= 0xE0) && (c_subChar <= 0xFE) && (c_subChar != 0xF7))) {
+			unsigned char c_ucSubChar = c_subChar - 'a' + 'A';
 			if (c_selfChar != c_ucSubChar) goto searchNext;
 		    } else {
 			goto searchNext;
@@ -4603,165 +5363,273 @@
     getOutOfHere: ;
 #endif /* ! __SCHTEAM__ */
 %}.
-    "/ arrive here if either not found, or invalid arguments
+
     notFound == true ifTrue:[
 	^ exceptionValue value.
     ].
-    ^ super indexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:caseSensitive
+
+    "/ arrive here aSubstring is a UnicodeString or arguments are invalid
+    ^ super
+	indexOfSubCollection:aSubString
+	startingAt:startIndex
+	ifAbsent:exceptionValue
+	caseSensitive:false
 
     "
-     'abcdefg' slowIndexOfSubCollection:'abc' startingAt:1 ifAbsent:nil caseSensitive:false
-     'abcdefg' slowIndexOfSubCollection:'bcd' startingAt:1 ifAbsent:nil caseSensitive:false
-     'abcdefg' slowIndexOfSubCollection:'cde' startingAt:1 ifAbsent:nil caseSensitive:false
-     'abcabcg' slowIndexOfSubCollection:'abc' startingAt:2 ifAbsent:nil caseSensitive:false
-
-     'ABCDEFG' slowIndexOfSubCollection:'abc' startingAt:1 ifAbsent:nil caseSensitive:false
-     'ABCDEFG' slowIndexOfSubCollection:'Abc' startingAt:1 ifAbsent:nil caseSensitive:false
-     'ABCDEFG' slowIndexOfSubCollection:'aBC' startingAt:1 ifAbsent:nil caseSensitive:false
-     'ABCDEFG' slowIndexOfSubCollection:'ABC' startingAt:1 ifAbsent:nil caseSensitive:false
-
-     'ABCDEFG' slowIndexOfSubCollection:'a' startingAt:1 ifAbsent:nil caseSensitive:false
-     'ABCDEFG' slowIndexOfSubCollection:'A' startingAt:1 ifAbsent:nil caseSensitive:false
-
-     'ABCDEFG' slowIndexOfSubCollection:'bcd' startingAt:1 ifAbsent:nil caseSensitive:false
-     'ABCDEFG' slowIndexOfSubCollection:'cde' startingAt:1 ifAbsent:nil caseSensitive:false
-     'ABCABCG' slowIndexOfSubCollection:'abc' startingAt:2 ifAbsent:nil caseSensitive:false
-
-     '1234567890' slowIndexOfSubCollection:'abc' startingAt:1 ifAbsent:nil caseSensitive:false
-     '1234567890' slowIndexOfSubCollection:'123' startingAt:1 ifAbsent:nil caseSensitive:false
-     '1234567890' slowIndexOfSubCollection:'123' startingAt:1 ifAbsent:nil caseSensitive:true
-     '1234567890' slowIndexOfSubCollection:'234' startingAt:1 ifAbsent:nil caseSensitive:true
-     '1234567890' slowIndexOfSubCollection:'345' startingAt:1 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:1 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:2 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:3 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:4 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:5 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:6 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:7 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:8 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:9 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:10 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'123' startingAt:11 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'231' startingAt:1 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'231' startingAt:3 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'231' startingAt:5 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'231' startingAt:6 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'231' startingAt:8 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'231' startingAt:9 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'2310' startingAt:6 ifAbsent:nil caseSensitive:true
-     '1231231231' slowIndexOfSubCollection:'2310' startingAt:8 ifAbsent:nil caseSensitive:true
+     'abcdefg' caseInsensitiveIndexOfSubCollection:'abc' startingAt:1 ifAbsent:nil
+     'abcdefg' caseInsensitiveIndexOfSubCollection:'bcd' startingAt:1 ifAbsent:nil
+     'abcdefg' caseInsensitiveIndexOfSubCollection:'cde' startingAt:1 ifAbsent:nil
+     'abcabcg' caseInsensitiveIndexOfSubCollection:'abc' startingAt:2 ifAbsent:nil
+
+     'ABCDEFG' caseInsensitiveIndexOfSubCollection:'abc' startingAt:1 ifAbsent:nil
+     'ABCDEFG' caseInsensitiveIndexOfSubCollection:'Abc' startingAt:1 ifAbsent:nil
+     'ABCDEFG' caseInsensitiveIndexOfSubCollection:'aBC' startingAt:1 ifAbsent:nil
+     'ABCDEFG' caseInsensitiveIndexOfSubCollection:'ABC' startingAt:1 ifAbsent:nil
+
+     'ABCDEFG' caseInsensitiveIndexOfSubCollection:'a' startingAt:1 ifAbsent:nil
+     'ABCDEFG' caseInsensitiveIndexOfSubCollection:'A' startingAt:1 ifAbsent:nil
+
+     'ABCDEFG' caseInsensitiveIndexOfSubCollection:'bcd' startingAt:1 ifAbsent:nil
+     'ABCDEFG' caseInsensitiveIndexOfSubCollection:'cde' startingAt:1 ifAbsent:nil
+     'ABCABCG' caseInsensitiveIndexOfSubCollection:'abc' startingAt:2 ifAbsent:nil
+
+     '1234567890' caseInsensitiveIndexOfSubCollection:'abc' startingAt:1 ifAbsent:nil
+     '1234567890' caseInsensitiveIndexOfSubCollection:'123' startingAt:1 ifAbsent:nil
     "
+
+    "Created: / 28-03-2017 / 15:33:50 / stefan"
+    "Modified (comment): / 28-03-2017 / 16:35:16 / stefan"
+!
+
+indexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:caseSensitive
+    "redefined as primitive for maximum speed (BM).
+     Compared to the strstr libc function, on my machine,
+     BM is faster for caseSensitive compares above around 8.5 searched characters.
+     For much longer searched strings, BM is much faster; 5times as fast for 20chars.
+     For caseInsensitive compares, strstr was found to be slower than caseInsensitiveIndexOf."
+
+    |notFound|
+
+%{  /* STACK:4000 */
+#ifndef __SCHTEAM__
+    if (__qIsStringLike(self)
+     && __isStringLike(aSubString)
+     && (__isSmallInteger(startIndex))
+     && (__intVal(startIndex) > 0)
+     && (caseSensitive==true)
+    ) {
+        unsigned char *haystack = __stringVal(self);
+        unsigned char *needle = __stringVal(aSubString);
+        int srchLen = __stringSize(aSubString);
+        int myLen = __stringSize(self);
+        int srchIdx = __intVal(startIndex) - 1;
+
+        if (srchLen == 0) {
+            #if 1
+                /* empty string does not match */
+                RETURN(__mkSmallInteger(0));
+            #else
+                /* empty string matches */
+                RETURN(startIndex);
+            #endif
+        } 
+        // console_fprintf(stderr, "myLen:%d, srchLen:%d, srchIdx:%d\n", myLen,srchLen,srchIdx);
+        if (srchIdx > (myLen - srchLen)) {
+            // console_fprintf(stderr, "srchIdx too large\n");
+            notFound = true;
+        } else {
+            if ( (srchLen > 4) /* && (myLen >= 30) */ ) {
+                #define MAX_PATTERN_SIZE 128
+                #define XSIZE 256
+                #define ASIZE 256
+                #define MAX(a,b) (a>b ? a : b)
+
+                // console_fprintf(stderr, "BM srchLen:%d\n", srchLen);
+                if (srchLen <= MAX_PATTERN_SIZE) {
+                    int i;
+                    static short lastPatternSize1 = 0;
+                    static char lastPattern1[MAX_PATTERN_SIZE+1] = { 0 };
+                    static short bmGs1[XSIZE+1], bmBc1[ASIZE];
+                    static short lastPatternSize2 = 0;
+                    static char lastPattern2[MAX_PATTERN_SIZE+1] = { 0 };
+                    static short bmGs2[XSIZE+1], bmBc2[ASIZE];
+                    short *bmGsX, *bmBcX;
+                    static short flipFlop = 0;
+
+                    #define preBmBc(x, m, bmBc) {         \
+                       int ii;                            \
+                                                          \
+                       for (ii = 0; ii < ASIZE; ++ii)     \
+                          bmBc[ii] = m;                   \
+                       for (ii = 0; ii < m - 1; ++ii)     \
+                          bmBc[x[ii]] = m - ii - 1;       \
+                    }
+
+                    #define suffixes(x, m, suff) {                      \
+                       int f, g, i;                                     \
+                                                                        \
+                       suff[m - 1] = m;                                 \
+                       g = m - 1;                                       \
+                       for (i = m - 2; i >= 0; --i) {                   \
+                          if (i > g && suff[i + m - 1 - f] < i - g)     \
+                             suff[i] = suff[i + m - 1 - f];             \
+                          else {                                        \
+                             if (i < g)                                 \
+                                g = i;                                  \
+                             f = i;                                     \
+                             while (g >= 0 && x[g] == x[g + m - 1 - f]) \
+                                --g;                                    \
+                             suff[i] = f - g;                           \
+                          }                                             \
+                       }                                                \
+                    }
+
+                    #define preBmGs(x, m, bmGs) {                       \
+                       int i, j, suff[XSIZE];                           \
+                                                                        \
+                       suffixes(x, m, suff);                            \
+                                                                        \
+                       for (i = 0; i < m; ++i)                          \
+                          bmGs[i] = m;                                  \
+                       j = 0;                                           \
+                       for (i = m - 1; i >= 0; --i)                     \
+                          if (suff[i] == i + 1)                         \
+                             for (; j < m - 1 - i; ++j)                 \
+                                if (bmGs[j] == m)                       \
+                                   bmGs[j] = m - 1 - i;                 \
+                       for (i = 0; i <= m - 2; ++i)                     \
+                          bmGs[m - 1 - suff[i]] = m - 1 - i;            \
+                    }
+
+                    /* tables only depend on pattern; 
+                     * so we can cache them in case the same string is searched again 
+                     * Here, two such tables are used alternatively
+                     * to remember the setup for the last two searches. 
+                     */
+                    if ((srchLen == lastPatternSize1) && (strcmp(lastPattern1, needle) == 0)) {
+                        /* tables1 still valid */
+                        // console_fprintf(stderr, "valid1: \"%s\"\n", lastPattern1);
+                        bmGsX = bmGs1; bmBcX = bmBc1;
+                    } else {
+                        if ((srchLen == lastPatternSize2) && (strcmp(lastPattern2, needle) == 0)) {
+                            /* tables1 still valid */
+                            // console_fprintf(stderr, "valid2: \"%s\"\n", lastPattern2);
+                            bmGsX = bmGs2; bmBcX = bmBc2;
+                        } else {
+                            if (flipFlop) {
+                                // console_fprintf(stderr, "cache in2 for: \"%s\"\n", needle);
+                                strcpy(lastPattern2, needle);
+                                lastPatternSize2 = srchLen;
+                                bmGsX = bmGs2; bmBcX = bmBc2;
+                            } else {
+                                // console_fprintf(stderr, "cache in1 for: \"%s\"\n", needle);
+                                strcpy(lastPattern1, needle);
+                                lastPatternSize1 = srchLen;
+                                bmGsX = bmGs1; bmBcX = bmBc1;
+                            }
+
+                            /* Preprocessing */
+                            // console_fprintf(stderr, "compute: \"%s\"\n", needle);
+                            preBmGs(needle, srchLen, bmGsX);
+                            preBmBc(needle, srchLen, bmBcX);
+
+                            flipFlop = 1-flipFlop;
+                        }
+                    }
+
+                    /* Searching */
+                    {
+                        int i;
+
+                        // console_fprintf(stderr, "srchIdx:%d; lRest:%d\n", srchIdx, (myLen - srchLen));
+                        while (srchIdx <= (myLen - srchLen)) {
+                            // console_fprintf(stderr, "srchIdx: %d\n", srchIdx);
+                            for (i = srchLen - 1; i >= 0 && needle[i] == haystack[i + srchIdx]; --i);
+                            if (i < 0) {
+                                RETURN (__mkSmallInteger(srchIdx+1));
+                            } else {
+                                short s1 = bmGsX[i];
+                                short s2 = bmBcX[haystack[i + srchIdx]] - srchLen + 1 + i;
+                                srchIdx += MAX(s1, s2);
+                            }
+                        }
+                    }
+                    notFound = true;
+                }
+            } else {
+                unsigned char *where;
+
+                switch (srchLen) {
+                    case 1:
+                        // console_fprintf(stderr, "strchr\n");
+                        where = (unsigned char *)strchr(haystack+srchIdx, needle[0]);
+                        break;
+                    case 2:
+                        // console_fprintf(stderr, "strstr2\n");
+                        {
+                            const unsigned char *h = haystack+srchIdx;
+
+                            uint16_t nw = needle[0]<<8 | needle[1], hw = h[0]<<8 | h[1];
+                            for (h++; *h && hw != nw; hw = hw<<8 | *++h);
+                            where = *h ? (unsigned char *)(h-1) : NULL;
+                        }
+                        break;
+                    case 3:
+                        // console_fprintf(stderr, "strstr3\n");
+                        {
+                            const unsigned char *h = haystack+srchIdx;
+
+                            uint32_t nw = needle[0]<<24 | needle[1]<<16 | needle[2]<<8;
+                            uint32_t hw = h[0]<<24 | h[1]<<16 | h[2]<<8;
+                            for (h+=2; *h && hw != nw; hw = (hw|*++h)<<8);
+                            where = *h ? (unsigned char *)(h-2) : NULL;
+                        }
+                        break;
+                    case 4:
+                        // console_fprintf(stderr, "strstr4\n");
+                        {
+                            const unsigned char *h = haystack+srchIdx;
+
+                            uint32_t nw = needle[0]<<24 | needle[1]<<16 | needle[2]<<8 | needle[3];
+                            uint32_t hw = h[0]<<24 | h[1]<<16 | h[2]<<8 | h[3];
+                            for (h+=3; *h && hw != nw; hw = hw<<8 | *++h);
+                            where = *h ? (unsigned char *)(h-3) : NULL;
+                        }
+                        break;
+                    default:
+                        // console_fprintf(stderr, "strstr\n");
+                        where = strstr((char *)(haystack+srchIdx), (char *)needle);
+                        break;
+                }
+                if (where != NULL) {
+                    RETURN (__mkSmallInteger(where-haystack + 1));    
+                }
+                notFound = true;
+            }
+        }
+    }
+#endif /* ! __SCHTEAM__ */
+%}.
+    notFound == true ifTrue:[
+        "/ Stderr showCR:'notFound.'.
+        ^ exceptionValue value.
+    ].
+
+    caseSensitive ifFalse:[
+        "/ Stderr showCR:'caseInsensitiveSearch...'.
+        ^ self caseInsensitiveIndexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue.
+    ].
+
+    "/ arrive here if aSubstring is a UnicodeString or arguments are invalid
+    ^ super indexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:true
+
+    "Modified: / 05-08-2012 / 12:27:31 / cg"
+    "Modified (comment): / 28-03-2017 / 16:31:54 / stefan"
+    "Modified (comment): / 12-03-2019 / 20:15:33 / Claus Gittinger"
 ! !
 
 !String methodsFor:'testing'!
 
-endsWith:aStringOrChar
-    "return true, if the receiver ends with something, aStringOrChar.
-     If aStringOrChar is an empty string, true is returned"
-
-%{  /* NOCONTEXT */
-#ifndef __SCHTEAM__
-    int len1, len2;
-    REGISTER unsigned char *src1, *src2;
-    unsigned char c;
-    REGISTER OBJ slf = self;
-
-    if (__isStringLike(slf) && __isStringLike(aStringOrChar)) {
-	len1 = __qSize(slf);
-	len2 = __qSize(aStringOrChar);
-	if (len1 < len2) {
-	    RETURN ( false );
-	}
-
-	src1 = __stringVal(slf) + (len1 - len2);
-	src2 = __stringVal(aStringOrChar);
-	while ((c = *src2++) != '\0') {
-	    if (c != *src1++) {
-		RETURN ( false );
-	    }
-	}
-	RETURN (true);
-    }
-    if (__isCharacter(aStringOrChar)) {
-	int val;
-
-	val = __intVal(__characterVal(aStringOrChar));
-	if ((unsigned)val <= 0xFF) {
-	    len1 = __stringSize(slf);
-	    if (len1 > 0) {
-		RETURN ( (__stringVal(slf)[len1-1] == val) ? true : false);
-	    }
-	}
-	RETURN ( false );
-    }
-#endif /* ! __SCHTEAM__ */
-%}.
-    ^ super endsWith:aStringOrChar
-
-    "
-     'hello world' endsWith:'world'
-     'hello world' endsWith:'earth'
-     'hello world' endsWith:$d
-     'hello world' endsWith:$e
-     '' endsWith:$d
-     'hello world' endsWith:#($r $l $d)
-     'hello world' endsWith:''
-    "
-!
-
-isBlank
-    "return true, if the receiver's size is 0 or if it contains only spaces.
-     Q: should we care for whiteSpace in general here ?"
-
-%{  /* NOCONTEXT */
-#ifndef __SCHTEAM__
-    REGISTER unsigned char *src;
-    REGISTER unsigned char c;
-    OBJ cls;
-
-    src = __stringVal(self);
-    if ((cls = __qClass(self)) != String)
-	src += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-
-# ifdef UINT64
-    while (*((UINT64 *)src) == 0x2020202020202020L) {
-	src += 8;
-    }
-# endif /* UINT64 */
-
-    while (*((unsigned *)src) == 0x20202020) {
-	src += 4;
-    }
-
-    while ((c = *src++) == ' ')
-	;; /* just walking along */
-    if (c != '\0') {
-	RETURN ( false );
-    }
-    RETURN ( true );
-# endif /* ! __SCHTEAM__ */
-%}.
-    ^ super isBlank
-!
-
-isEmpty
-    "return true if the receiver is empty (i.e. if size == 0)
-     Redefined here for performance"
-
-%{  /* NOCONTEXT */
-#ifndef __SCHTEAM__
-    OBJ cls;
-
-    cls = __qClass(self);
-    if ((cls == String) || (cls == Symbol)) {
-	RETURN ( (__stringSize(self) == 0) ? true : false);
-    }
-#endif /* ! __SCHTEAM__ */
-%}.
-    ^ self size == 0
-!
-
 isLiteral
     "return true, if the receiver can be used as a literal constant in ST syntax
      (i.e. can be used in constant arrays)"
@@ -4769,264 +5637,14 @@
     ^ true
 !
 
-levenshteinTo:aString s:substWeight k:kbdTypoWeight c:caseWeight i:insrtWeight d:deleteWeight
-    "parametrized levenshtein. arguments are the costs for
-     substitution, case-change, insertion and deletion of a character."
-
-%{  /* STACK: 2000 */
-#ifndef __SCHTEAM__
-    /*
-     * this is very heavy used when correcting errors
-     * (all symbols are searched for best match) - therefore it must be fast
-     */
-
-    unsigned short *data;
-    int l1, l2;
-    REGISTER int sz;
-    unsigned char *s1, *s2;
-    int v1, v2, v3;
-    INT m;
-    REGISTER unsigned short *dp;
-    REGISTER int rowDelta;
-    REGISTER int j;
-    int i;
-    int iW, cW, sW, kW, dW;
-#   define FASTSIZE 30  /* increase STACK if you increase this ... */
-    unsigned short fastData[(FASTSIZE + 1) * (FASTSIZE + 1)];
-    extern void *malloc();
-
-    if (__qIsStringLike(self) && __isStringLike(aString)
-	&& __bothSmallInteger(insrtWeight, caseWeight)
-	&& __bothSmallInteger(substWeight, deleteWeight)
-	&& __isSmallInteger(kbdTypoWeight)
-    ) {
-	iW = __intVal(insrtWeight);
-	cW = __intVal(caseWeight);
-	sW = __intVal(substWeight);
-	kW = __intVal(kbdTypoWeight);
-	dW = __intVal(deleteWeight);
-	s1 = __stringVal(self);
-	s2 = __stringVal(aString);
-	l1 = __stringSize(self);
-	l2 = __stringSize(aString);
-
-	sz = (l1 < l2) ? l2 : l1;
-	rowDelta = sz + 1;
-	if (sz <= FASTSIZE) {
-	    data = fastData;
-	} else {
-	    /* add ifdef ALLOCA here ... */
-	    data = (unsigned short *)malloc(rowDelta * rowDelta * sizeof(short));
-	    if (! data) goto mallocFailed;
-	}
-
-	data[0] = 0;
-	for (j=1, dp=data+1; j<=sz; j++, dp++)
-	    *dp = dp[-1] + iW;
-
-	for (i=1, dp=data+rowDelta; i<=sz; i++, dp+=rowDelta)
-	    *dp = dp[-rowDelta] + dW;
-
-	for (i=0; i<l1; i++) {
-	    for (j=0; j<l2; j++) {
-		if (s1[i] == s2[j])
-		    m = 0;
-		else if (tolower(s1[i]) == tolower(s2[j]))
-		    m = cW;
-		else if (sW != kW && nextOnKeyboard(tolower(s1[i]), tolower(s2[j])))
-		    m = kW;
-		else
-		    m = sW;
-
-		dp = data + ((i+1)*rowDelta) + j;
-		v2 = dp[0] + iW;
-		v1 = dp[-rowDelta] + m;
-		v3 = dp[-rowDelta+1] + dW;
-		if (v1 < v2) {
-		    if (v1 < v3)
-			m = v1;
-		    else
-			m = v3;
-		} else {
-		    if (v2 < v3)
-			m = v2;
-		    else
-			m = v3;
-		}
-		dp[1] = m;
-	    }
-	}
-	m = data[l1*rowDelta + l2];
-	if (sz > FASTSIZE)
-	    free(data);
-	RETURN ( __mkSmallInteger(m) );
-    }
-mallocFailed: ;
-#endif /* ! __SCHTEAM__ */
-%}.
-
-    ^ super levenshteinTo:aString
-			s:substWeight k:kbdTypoWeight c:caseWeight
-			i:insrtWeight d:deleteWeight
-
-    "
-     'ocmprt' levenshteinTo:'computer'
-     'computer' levenshteinTo:'computer'
-     'ocmputer' levenshteinTo:'computer'
-     'cmputer' levenshteinTo:'computer'
-     'computer' levenshteinTo:'cmputer'
-     'computer' levenshteinTo:'vomputer'
-     'computer' levenshteinTo:'bomputer'
-     'Computer' levenshteinTo:'computer'
-    "
-!
-
-notEmpty
-    "return true if the receiver is not empty (i.e. if size ~~ 0)
-     Redefined here for performance"
-
-%{  /* NOCONTEXT */
-#ifndef __SCHTEAM__
-    OBJ cls;
-
-    cls = __qClass(self);
-    if ((cls == String) || (cls == Symbol)) {
-	RETURN ( (__stringSize(self) != 0) ? true : false);
-    }
-#endif /* ! __SCHTEAM__ */
-%}.
-    ^ self size ~~ 0
-!
-
-startsWith:aStringOrChar
-    "return true, if the receiver starts with something, aStringOrChar.
-     If the argument is empty, true is returned.
-     Notice, that this is similar to, but slightly different from VW's and Squeak's beginsWith:,
-     which are both inconsistent w.r.t. an empty argument."
-
-%{  /* NOCONTEXT */
-#ifdef __SCHTEAM__
-    if (self.isSTString()) {
-	if (aStringOrChar.isSTString()) {
-	    java.lang.String me = self.asString();
-	    java.lang.String other = aStringOrChar.asString();
-	    return __c__._RETURN( me.startsWith(other) ? STObject.True : STObject.False);
-	}
-	if (aStringOrChar.isSTCharacter()) {
-	    char[] me = self.asSTString().characters;
-	    char ch = aStringOrChar.charValue();
-	    return __c__._RETURN( ((me.length > 0)
-				  && (me[0] == ch)) ? STObject.True : STObject.False);
-	}
-    }
-#else
-    int len1, len2;
-    REGISTER unsigned char *src1, *src2;
-    unsigned char c;
-    REGISTER OBJ slf = self;
-
-    if (__qIsStringLike(slf) &&__isStringLike(aStringOrChar)) {
-	src1 = __stringVal(slf);
-	src2 = __stringVal(aStringOrChar);
-
-	if (src1[0] != src2[0]) {
-	    if (__qSize(aStringOrChar) == (OHDR_SIZE+1) /* 1 for the 0-byte */) {
-		RETURN (true);
-	    }
-	    RETURN ( false );
-	}
-
-	len1 = __qSize(slf);
-	len2 = __qSize(aStringOrChar);
-	if (len1 < len2) {
-	    RETURN ( false );
-	}
-
-# ifdef UINT64
-	while (len2 > (OHDR_SIZE+sizeof(UINT64))) {
-	    if ( ((UINT64 *)src1)[0] != ((UINT64 *)src2)[0] ) {
-		RETURN (false);
-	    }
-	    len2 -= sizeof(UINT64);
-	    src1 += sizeof(UINT64);
-	    src2 += sizeof(UINT64);
-	}
-# else
-#  ifdef __UNROLL_LOOPS__
-	while (len2 > (OHDR_SIZE+sizeof(INT)*4)) {
-	    if ( ((unsigned INT *)src1)[0] != ((unsigned INT *)src2)[0]) {
-		RETURN (false);
-	    }
-	    if ( ((unsigned INT *)src1)[1] != ((unsigned INT *)src2)[1]) {
-		RETURN (false);
-	    }
-	    if ( ((unsigned INT *)src1)[2] != ((unsigned INT *)src2)[2]) {
-		RETURN (false);
-	    }
-	    if ( ((unsigned INT *)src1)[3] != ((unsigned INT *)src2)[3]) {
-		RETURN (false);
-	    }
-	    len2 -= sizeof(INT)*4;
-	    src1 += sizeof(INT)*4;
-	    src2 += sizeof(INT)*4;
-	}
-#  endif /* __UNROLL_LOOPS__ */
-# endif /* UINT64 */
-
-	while (len2 > (OHDR_SIZE+sizeof(INT))) {
-	    if ( ((unsigned INT *)src1)[0] != ((unsigned INT *)src2)[0]) {
-		RETURN (false);
-	    }
-	    len2 -= sizeof(INT);
-	    src1 += sizeof(INT);
-	    src2 += sizeof(INT);
-	}
-
-	while ((c = *src2++) != '\0') {
-	    if (c != *src1) {
-		RETURN ( false );
-	    }
-	    src1++;
-	}
-	RETURN (true);
-    }
-    if (__isCharacter(aStringOrChar)) {
-	int val;
-
-	val = __intVal(__characterVal(aStringOrChar));
-	if ((unsigned)val <= 0xFF) {
-	    len1 = __stringSize(slf);
-	    if (len1 > 0) {
-		RETURN ( (__stringVal(slf)[0] == val) ? true : false);
-	    }
-	}
-	RETURN ( false );
-    }
-#endif /* not __SCHTEAM__ */
-%}.
-    ^ super startsWith:aStringOrChar
-
-    "
-     'hello world' startsWith:'hello'
-     'hello world' startsWith:'hella'
-     'hello world' startsWith:'hi'
-     'hello world' startsWith:$h
-     'hello world' startsWith:$H
-     'hello world' startsWith:(Character value:16rFF00)
-     'hello world' startsWith:60
-     'hello world' startsWith:#($h $e $l)
-     'hello world' startsWith:''
-    "
-! !
-
-!String methodsFor:'tracing'!
-
 isSingleByteString
     "returns true only for strings and immutable strings.
      Must replace foo isMemberOf:String and foo class == String"
 
     ^ true
-!
+! !
+
+!String methodsFor:'tracing'!
 
 traceInto:aRequestor level:level from:referrer
     "double dispatch into tracer, passing my type implicitely in the selector"
@@ -5036,6 +5654,7 @@
 
 ! !
 
+
 !String class methodsFor:'documentation'!
 
 version