eXept Software AG Logo

Smalltalk/X Webserver

Documentation of class 'CharacterArray':

Home

Documentation
www.exept.de
Everywhere
for:
[back]

Class: CharacterArray


Inheritance:

   Object
   |
   +--Collection
      |
      +--SequenceableCollection
         |
         +--ArrayedCollection
            |
            +--UninterpretedBytes
               |
               +--CharacterArray
                  |
                  +--FourByteString
                  |
                  +--String
                  |
                  +--Text
                  |
                  +--TwoByteString

Package:
stx:libbasic
Category:
Collections-Text
Version:
rev: 1.1005 date: 2024/04/23 08:34:05
user: stefan
file: CharacterArray.st directory: libbasic
module: stx stc-classLibrary: libbasic

Description:


CharacterArray is a superclass for all kinds of Strings (i.e.
(singleByte-)Strings, TwoByteStrings, UnicodeStrings
and whatever may come in the future.

This class is abstract, meaning that there are no instances of it;
concrete subclasses define how the characters are stored (i.e. either as
single byte, two-byte or four byte strings).

All this class does is provide common protocol for concrete subclasses.

Notice:
    internally, ST/X uses a unicode encoding for ALL characters - both
    for individual character entities and for strings of characters.
    When reading/writing files in different encodings, the conversion is
    done at read/write time by use of a CharacterEncoder instance.
    These know how to convert to a wide range of encodings.

Also notice:
    UTF8 and UTF16 are external encodings of a Unicode string; they are never
    used internally. When interacting with a UTF8 interface (OS-API or files),
    you should convert UTF8 into the internal full Unicode right at the interface.
    Do not keep UTF8 around internally as String instances.
    The reason is that UTF8 makes it harder to manipulate strings (for example
    to insert/extract substrings or to get its size. Such operations would
    require a scan of the UTF8, which would complicate them).
    Of course, there may be rare exceptions to this, for example if a file's contents
    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.

copyright

COPYRIGHT (c) 1994 by Claus Gittinger All Rights Reserved This software is furnished under a license and may be used only in accordance with the terms of that license and with the inclusion of the above copyright notice. This software may not be provided or otherwise made available to, or used by, any other person. No title to or ownership of the software is hereby transferred.

Class protocol:

Compatibility-VW
o  fromIntegerArray: anArray
Answer a new instance of the receiver that is created from the argument, anArray.

Usage example(s):

     String fromIntegerArray: #[8 127]

Signal constants
o  decodingFailedSignal
return the signal, raised when decoding of a string is not possible
due to invalid characters contained in the source.
This may happen for example, if a non EUC coded 8-bit string
is attempted to be decoded into a JIS string.

o  encodingFailedSignal
return the (query-) signal, raised when encoding of a string is not possible
due to invalid characters contained in the source.

cleanup
o  lowSpaceCleanup
cleanup in low-memory situations

Usage example(s):

     CharacterArray lowSpaceCleanup

encoding & decoding
o  deadKeyLanguage: aLanguage

o  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...

Usage example(s):

     self deadKeyMap

o  deadKeyMapForLanguage: lang
returns a subset of the full dead key map, useful when editing a specific language texts
(it is disrupting, to get dead-keys for every possible character;
using one of these maps limits the processing to those characters, which are actually
used in the language)

Usage example(s):

     self deadKeyMapForLanguage:#de
     self deadKeyMapForLanguage:#fr

o  deadKeyMapsPerLanguage

o  decodeFromUTF8: aStringOrByteCollection
given a string or bytes in UTF8 encoding,
return a new string containing the same characters, in Unicode encoding.
Returns either a normal String, a Unicode16String or a Unicode32String instance.
This is only useful, when reading from external sources or communicating with
other systems
(ST/X never uses utf8 internally, but always uses strings of fully decoded unicode characters).
This only handles up-to 30bit characters.

Usage example(s):

     CharacterArray decodeFromUTF8:#[ 16r41 16r42 ]
     CharacterArray decodeFromUTF8:#[ 16rC6 16r8F ]
     CharacterArray decodeFromUTF8:#[ 16rEF 16rBF 16rBF ]

   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 ]

   invalid:
     CharacterArray decodeFromUTF8:#[ 16rC0 16r80 ]
     CharacterArray decodeFromUTF8:#[ 16rE0 16r80 16r80 ]
     CharacterArray decodeFromUTF8:#[ 16rE0 16r81 16r02 ]

o  setupNormalizationAndDeadKeyMaps
returns a 2-stage map from ch2 -> ch1 -> mappedChar.
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. $Ä).
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...

Usage example(s):

     self setupNormalizationAndDeadKeyMaps

o  unicodeDenormalizationMap
returns a 2-stage map from ch2 -> ch1 -> mappedChar
for unicode normalization (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...

Usage example(s):

     self unicodeDenormalizationMap

o  unicodeNormalizationMap
returns a 2-stage map from ch2 -> ch1 -> mappedChar
for unicode normalization (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...

Usage example(s):

     self unicodeNormalizationMap

initialization
o  initialize
CharacterArray initialize

instance creation
o  basicNew
return a new empty string

o  fromBytes: aByteCollection
return an instance of the receiver class,
taking untranslated bytes from the argument, aByteCollection
in most-significant first order.
Only useful, when reading twoByteStrings from external sources.

Usage example(s):

     Unicode16String fromBytes:#[16r02 16r20]
     Unicode16String fromBytes:#[16r02 16r20] MSB:true
     Unicode16String fromBytes:#[16r02 16r20] MSB:false

o  fromBytes: aByteCollection MSB: msb
return an instance of the receiver class,
taking untranslated bytes from the argument, aByteCollection
in the given byte order.
Only useful, when reading twoByteStrings from external sources.

Usage example(s):

     Unicode16String fromBytes:#[16r02 16r20]

o  fromString: aString
return a copy of the argument, aString

Usage example(s):

        Unicode16String fromString:'hello'
        String fromString:'hello' asUnicode16String
        Unicode16String fromString:'hello' asUnicode16String

o  fromStringCollection: aCollectionOfStrings
return a new string formed by concatenating each in aCollectionOfStrings

Usage example(s):

     String fromStringCollection:#('hello' 'world' 'how' 'about' 'this')

o  fromStringCollection: aCollectionOfStrings separatedBy: aSeparatorString
return a new string formed by concatenating each in aCollectionOfStrings
separating them by aSeparatorString

Usage example(s):

     String fromStringCollection:#('hello' 'world' 'how' 'about' 'this') separatedBy:' '
     String fromStringCollection:#('hello' 'world' 'how' 'about' 'this') separatedBy:'Ƞ'
     Text fromStringCollection:{'hello'. 'world'. 'how' allBold. 'about'. 'this'. 'äöü'} separatedBy:'Ƞ'

o  fromUTF8Bytes: aByteCollection
Modified (comment): / 07-02-2017 / 17:32:38 / stefan

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  new
return a new empty string

o  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.
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)

Usage example(s):

     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'] 

o  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.

Usage example(s):

     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']

o  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.

Usage example(s):

     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']

o  writeStreamClass
the type of stream used in writeStream.
Here, we return CharacterWriteStream, which automatically changes
the underlying collection to a multiByte string (i.e. UnicodeString).
So you can stream wide characters into it.

pattern matching
o  matchEscapeCharacter
return the character used to escape a matchCharacter
(i.e. make it a regular character in a matchPattern)

o  matchScan: matchScanArray from: matchStart to: matchStop with: aString from: start to: stop caseSensitive: caseSensitive
helper for match; return true if the characters from start to stop in
aString are matching the scan in matchScan from matchStart to matchStop.
The matchScan is as created by asMatchScanArray.

This algorithm is not at all the most efficient;
for heavy duty pattern matching, an interface (primitive) to the regex
pattern matching package should be added.

Usage example(s):

     |scanArray s|

     scanArray := self matchScanArrayFrom:'*hello'.
     s := 'foo bar hello world'.
     CharacterArray
         matchScan:scanArray
         from:1
         to:scanArray size
         with:s
         from:1
         to:s size
         caseSensitive:true

Usage example(s):

     |scanArray s|

     scanArray := self matchScanArrayFrom:'*hello*'.
     s := 'foo bar hello world'.
     CharacterArray
         matchScan:scanArray
         from:1
         to:scanArray size
         with:s
         from:1
         to:s size
         caseSensitive:true

o  matchScan: matchScanArray from: matchStart to: matchStop with: aString from: start to: stop ignoreCase: ignoreCase
helper for match; return true if the characters from start to stop in
aString are matching the scan in matchScan from matchStart to matchStop.
The matchScan is as created by asMatchScanArray.

This algorithm is not at all the most efficient;
for heavy duty pattern matching, an interface (primitive) to the regex
pattern matching package should be added.

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  matchScanArrayFrom: aString
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).
Returns nil for invalid patterns

Usage example(s):

     String matchScanArrayFrom:'*ute*'
     String matchScanArrayFrom:'**ute**'
     String matchScanArrayFrom:'*uter'
     String matchScanArrayFrom:'\*uter'
     String matchScanArrayFrom:'[cC]#mpute[rR]'
     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]'

o  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).
Returns nil for invalid patterns (should be changed now to raise an error)

Usage example(s):

     String matchScanArrayFrom:'*ute*'  
     String matchScanArrayFrom:'**ute**'
     String matchScanArrayFrom:'*uter'
     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]'
     String matchScanArrayFrom:'[A-Z$_][A-Za-z0-9$\[\]]*'
     String matchScanArrayFrom:'[A-Z$\[\]]*'
     String matchScanArrayFrom:'[A-Z$_\[][A-Za-z0-9$\-\] ]*'

     String matchScanArrayFrom:'abc#'    
     String matchScanArrayFrom:'*#*'    
     String matchScanArrayFrom:'\[a-' escapeCharacter:$\
     .

queries
o  isAbstract
Return if this class is an abstract class.
True is returned for CharacterArray here; false for subclasses.
Abstract subclasses must redefine this again.

o  speciesForCharacterSize: characterSize
answer the class, that is able to hold characters of size characterSize

utilities
o  through: aCharacter in: inStream
read all characters through aCharacter and return a
dense strings for it (i.e. String/TwoByteString, if possible).
This helper is present because when reading from a unicode32 stream,
dense strings are preferred.
If inStream is known to return single byte characters,
you should better use inStream through:aCharacter

o  throughAny: aCollection in: inStream
read all characters through any in aCollection and return a
dense strings for it (i.e. String/TwoByteString, if possible).
This helper is present because when reading from a unicode32 stream,
dense strings are preferred.
If inStream is known to return single byte characters,
you should better use inStream throughAny:aCollection

o  withoutAmpersandEscapes: label
remove single ampersands;
replace double ampersands by single ones.
This is used to unescape menu-labels
(which use the ampersand as shortKey marker)

Usage example(s):

     String withoutAmpersandEscapes:''
     String withoutAmpersandEscapes:'a'
     String withoutAmpersandEscapes:'abcd'
     String withoutAmpersandEscapes:'&abcd'
     String withoutAmpersandEscapes:'&abcd&'
     String withoutAmpersandEscapes:'&a&b&c&d'
     String withoutAmpersandEscapes:'&a&b&c&d&'
     String withoutAmpersandEscapes:'&&a&&b&&c&&d&&'
     String withoutAmpersandEscapes:'&&a&&b&&c&&d&'
     String withoutAmpersandEscapes:'&a&&b&&c&&d&'
     String withoutAmpersandEscapes:'a&&b&&c&&d'


Instance protocol:

Compatibility-ANSI
o  addLineDelimiters
Ansi compatibility - same as withCRs

Compatibility-Dolphin
o  copyExpanding: expandTable
( an extension from the stx:libcompat package )
return a copy of myself, with translations from the expandTable sliced in.
The argument is supposed to map from characters to either characters or strings.
Added for Dolphin compatibility

Usage example(s):

     'hello' copyExpanding:(Dictionary withKeys:{$h . $e . $o} andValues:{'HH' . 'EE' . $O })

o  formatWith: aString
( an extension from the stx:libcompat package )
Compatibility method - do not use in new code.
same as #bindWith: for Dolphin compatibility

Usage example(s):

     'hello%1world' formatWith:'123'

o  formatWith: arg1 with: arg2
( an extension from the stx:libcompat package )
Compatibility method - do not use in new code.
same as #bindWith: for Dolphin compatibility

Usage example(s):

     'hello%1 %2world' formatWith:'123' with:234

o  formatWith: arg1 with: arg2 with: arg3
( an extension from the stx:libcompat package )
Compatibility method - do not use in new code.
same as #bindWith: for Dolphin compatibility

Usage example(s):

     'hello%1 %2 %3world' formatWith:'123' with:234 with:345

o  lines
( an extension from the stx:libcompat package )
return the receiver as a collection of lines.
Added for Dolphin compatibility

Usage example(s):

     'hello world' lines  

     'foo
bar
baz' lines

o  substrings: separatorCharacterOrString
( an extension from the stx:libcompat package )
return a collection consisting of all words contained in the receiver.
Words are separated by separatorCharacter.
This is similar to split: (squeak), asCollectionOfSubstringsSeparatedBy: (st/x)
and the same as subStrings: (with UC 'S' in V'age)
and has been added for Dolphin compatibility.

Usage example(s):

     'foo:bar:baz:smalltalk' substrings:$:
     'foo:bar:baz:smalltalk' substrings:':'
     'foo.bar,baz-smalltalk' substrings:'.,-'

o  truncateTo: smallSize
( an extension from the stx:libcompat package )
return myself or a copy shortened to smallSize. 1/18/96 sw

Usage example(s):

     'hello world' truncateTo:5  
     'hello' truncateTo:10     

     'hello world' copyTo:5
     'hello' copyTo:10

Compatibility-GNU
o  % anArrayOfOperands
return a copy of the receiver, where a '%i' escape
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.

Usage example(s):

     'do you prefer %1 or rather %2 (not talking about %3) ?'
        % #('smalltalk' 'c++' 'c')

     'do you %(what) ?'
        % (Dictionary new at:#'what' put:'understand'; yourself)

Compatibility-ST/V
o  asArrayOfSubstrings
return an array of substrings from the receiver, interpreting
separators (i.e. spaces & newlines) as word-delimiters.
This has been added for ST/V compatibility
- the actual work is done in asCollectionOfWords.
(sigh: it is called #'subStrings' in V'Age, #'substrings' in Squeak
and #'asCollectionOfWords' in ST/X)

Usage example(s):

     '1 one two three four 5 five' asArrayOfSubstrings
     '1
one
        two three four 5 five' asArrayOfSubstrings

o  equalsIgnoreCase: aString
( an extension from the stx:libcompat package )
This is an ST/V compatibility method and an alias for sameAs:.

Usage example(s):

     'abc' equalsIgnoreCase: 'aBC'

o  replChar: oldChar with: newChar
( an extension from the stx:libcompat package )
return a copy of the receiver, with all oldChars replaced by newChar.
This is an ST/V compatibility method and an alias for copyReplaceAll.

Usage example(s):

     '12345678901234567890' replChar:$0 with:$*

o  replChar: oldChar withString: newString
( an extension from the stx:libcompat package )
return a copy of the receiver, with all oldChars replaced
by newString (i.e. slice in the newString in place of the oldChar).
This is an ST/V compatibility method.

Usage example(s):

     '12345678901234567890' replChar:$0 withString:'foo'    => '123456789foo123456789foo'
     'a string with spaces' replChar:$  withString:' foo '  => 'a foo string foo with foo spaces'

o  replString: subString withString: newString
( an extension from the stx:libcompat package )
return a copy of the receiver, with all sequences of subString replaced
by newString (i.e. slice in the newString in place of the oldString).
This is an ST/V compatibility method and an alias for copyReplaceString.

Usage example(s):

     '12345678901234567890' replString:'123' withString:'OneTwoThree'
     '12345678901234567890' replString:'123' withString:'*'
     '12345678901234567890' replString:'234' withString:'foo'

     ('a string with spaces' replChar:$  withString:' foo ')
        replString:'foo' withString:'bar'

o  subString: start to: end
( an extension from the stx:libcompat package )
same as copyFrom:to:
This is an ST/V compatibility method and an alias for copyFrom:to:.

Usage example(s):

     '12345678901234567890' subString:3 to:8

o  trimBlanks
return a copy of the receiver without leading and trailing spaces.
This is an ST/V compatibility method and an alias for withoutSpaces.

Usage example(s):

     '    spaces at beginning' trimBlanks
     'spaces at end    ' trimBlanks
     '    spaces at beginning and end     ' trimBlanks
     'no spaces' trimBlanks

o  uncapitalized
( an extension from the stx:libcompat package )
Answer a <readableString> which is a copy of the receiver but with
the first character converted to its lowercase equivalent.

Compatibility-Squeak
o  asBoldText
return self as a bold text

o  asDate
Many allowed forms, see Date.readFrom:

Usage example(s):

     '30 Apr 1999' asDate dayName capitalized

o  asFileReference
( an extension from the stx:libcompat package )
Squeak mimikri

o  asOneByteString
( an extension from the stx:libcompat package )
return the receiver converted to a 'normal' string.
Same as asSingleByteString - for Squeak/Pharo compatibility.

o  asTime
Many allowed forms, see Time.readFrom:

Usage example(s):

     '14:22:05' asTime      => 14:22:05
     '02:22:05 am' asTime   => 02:22:05
     '02:22:05 pm' asTime   => 14:22:05

o  asUrl
( an extension from the stx:libcompat package )
Same as asURL - for Squeak/Pharo compatibility.

o  asWideString
( an extension from the stx:libcompat package )
return a two-byte string containing the same characters as the receiver.
Same as asTwoByteString - for Squeak/Pharo compatibility.

Usage example(s):

     'abc' asWideString

o  beginsWith: aStringOrCharacter caseSensitive: caseSensitive
( an extension from the stx:libcompat package )
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.

o  capitalized
( an extension from the stx:libcompat package )
same as asUppercaseFirst for Squeak/Pharo compatibility

Usage example(s):

     'hello' capitalized

o  caseInsensitiveLessOrEqual: aString
( an extension from the stx:libcompat package )
compare the receiver against the argument ignoring case differences
For Squeak/Pharo compatibility

o  caseSensitiveLessOrEqual: aString
( an extension from the stx:libcompat package )
compare the receiver against the argument caring for case differences
For Squeak/Pharo compatibility

o  charactersExactlyMatching: aString
( an extension from the stx:libcompat package )
marked as obsolete by exept MBP at 11-03-2022

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  convertToEncoding: nameOfEncoding
( an extension from the stx:libcompat package )
special case, because it is so common:

Usage example(s):

     'hellöäü' convertToEncoding:'utf8'
     'hello' convertToEncoding:'cp1252'

o  displayProgressAt: aPoint from: startValue to: endValue during: actionExpectingProgressHolder
( an extension from the stx:libcompat package )

o  findDelimiters: delimiters startingAt: start
( an extension from the stx:libcompat package )
Answer the index of the character within the receiver, starting at start,
that matches one of the delimiters.
If the receiver does not contain any of the delimiters, answer size + 1.

o  findLastOccurrenceOfString: aString startingAt: startIndex
( an extension from the stx:libcompat package )
this does a forward search starting at startIndex,
as opposed to lastIndexOfString:startingAt:, which searches backwards from the index

Usage example(s):

     'foo' findLastOccurrenceOfString:' ' startingAt:1       -> 0
     'foo bar' findLastOccurrenceOfString:' ' startingAt:1   -> 4
     'foo bar ' findLastOccurrenceOfString:' ' startingAt:1  -> 8

o  findString: key startingAt: start caseSensitive: caseSensitive

o  findTokens: delimiterOrDelimiters
( an extension from the stx:libcompat package )
cg: I am not sure, if this is really the squeak semantics (w.r.t. empty fields)

Usage example(s):

     'a|b#c||e' findTokens:#($# $|) => StringCollection('a' 'b' 'c' 'e')
     'a|b#c||e' findTokens:$|       => StringCollection('a' 'b#c' '' 'e')
     'a b c e' findTokens:' '       => StringCollection('a' 'b' 'c' 'e')
     'a::b::c::e' findTokens:'::'   => StringCollection('a' 'b' 'c' 'e')
     c'a\r\nb\r\nc\r\ne' findTokens:c'\r\n'                               => StringCollection('a' 'b' 'c' 'e')
     c'a\r\nb\r\nc\r\ne' findTokens:{Character return . Character lf}     => StringCollection('a' 'b' 'c' 'e')

o  findTokens: delimiters keep: keepers
( an extension from the stx:libcompat package )
Answer the collection of tokens that result from parsing self.
The tokens are seperated by delimiters, any of a string of characters.
If a delimiter is also in keepers, make a token for it.
(Very useful for carriage return.
A sole return ends a line, but is also saved as a token so you can see where the line breaks were.)

o  format: collection
( an extension from the stx:libcompat package )
similar to bindWith but different syntax,
format the receiver by slicing in elements from collection, as in the following examples:
('Five is {1}.' format: { 1 + 4}) >>> 'Five is 5.'
('Five is {five}.' format: (Dictionary with: #five -> 5)) >>> 'Five is 5.'
('In {1} you can escape \{ by prefixing it with \\' format: {'strings'}) >>> 'In strings you can escape { by prefixing it with \'
('In \{1\} you can escape \{ by prefixing it with \\' format: {'strings'}) >>> 'In {1} you can escape { by prefixing it with \'

o  includesSubString: aString
( an extension from the stx:libcompat package )
return true, if a substring is contained in the receiver.
The compare is case sensitive.

Usage example(s):

     'hello world' includesSubString:'Hel'
     'hello world' includesSubString:'hel'
     'hello world' includesSubString:'llo'

o  includesSubString: aString caseSensitive: caseSensitive
( an extension from the stx:libcompat package )
sigh - an alias; added for Squeak/Pharo compatibility

o  includesSubstring: aString
( an extension from the stx:libcompat package )
sigh - an alias; added for Squeak/Pharo compatibility

o  includesSubstring: aString caseSensitive: caseSensitive
( an extension from the stx:libcompat package )
return true, if a substring is contained in the receiver.
The argument, caseSensitive controls if case is ignored in the compare.

Usage example(s):

     'hello world' includesSubstring:'Hel' caseSensitive:true
     'hello world' includesSubstring:'Hel' caseSensitive:false

     'hello world' includesString:'Hel' caseSensitive:true
     'hello world' includesString:'Hel' caseSensitive:false

o  intervalFromStartLine: aStartLine startColumn: aStartColumn toEndLine: anEndLine endColumn: anEndColumn
( an extension from the stx:libcompat package )
Returns an interval spanning between startLine @ startColumn to endLine @ endColumn

o  intervalOfLine: aLineNumber
( an extension from the stx:libcompat package )
Answer an interval spanning between the first and the last character of the line from aLineNumber.
Use this to convert lineNr into a character range.

o  intervalOfLineCorrespondingToIndex: anIndex
( an extension from the stx:libcompat package )
Answer an interval spanning between the first and the last character of the line containing the given character index

o  isAllDigits
( an extension from the stx:libcompat package )
Answer whether the receiver's characters are all digits

Usage example(s):

     'hello world' isAllDigits
     '12344' isAllDigits

o  lastSpacePosition
( an extension from the stx:libcompat package )
return the index of the last space character; 0 if there is none.
Added for Squeak/Pharo compatibility

o  lineIndicesDo: aBlock
( an extension from the stx:libcompat package )
execute aBlock with 3 arguments for each line:
- start index of line
- end index of line without line delimiter
- end index of line including line delimiter(s) CR, LF or CRLF

o  linesDo: aBlock
evaluate the argument, aBlock for all lines,
up to the end

o  openInWorkspaceWithTitle: aTitleString
( an extension from the stx:libcompat package )
Added for Squeak/Pharo compatibility

o  padded: leftOrRight to: paddedSize with: padCharacter
pad left (leftOrRight == #left) or right

Usage example(s):

     'hello' padded:#right to:10 with:$.
     'hello' padded:#left to:10 with:$.

o  piecesCutWhereCamelCase
( an extension from the stx:libcompat package )
Breaks apart words written in camel case.

It's not simply using piecesCutWhere: because we want
to also deal with abbreviations and thus we need to
decide based on three characters, not just on two:

This is slightly different from the ST/X camelCaseSeparatedWords in that it handles digits
as separate words whereas the STX function adds them to the previous word.
Also the handling of spaces is different.

Usage example(s):

     ('FOOBar') piecesCutWhereCamelCase asArray                 => #('FOO' 'Bar').
     ('FOOBar12AndSomething') piecesCutWhereCamelCase asArray   => #('FOO' 'Bar' '12' 'And' 'Something')        
     ('FOOBar1AndSomething') piecesCutWhereCamelCase asArray    => #('FOO' 'Bar' '1' 'And' 'Something')        
     ('FOOBar1 12AndSomething') piecesCutWhereCamelCase asArray => #('FOO' 'Bar' '1' ' ' '12' 'And' 'Something')        
     ('FOOBar1 AndSomething') piecesCutWhereCamelCase asArray   => #('FOO' 'Bar' '1' ' And' 'Something')      

     ('FOOBar') camelCaseSeparatedWords asArray                 => #('FOO' 'Bar').
     ('FOOBar1AndSomething') camelCaseSeparatedWords asArray    => #('FOO' 'Bar1' 'And' 'Something')        
     ('FOOBar1 12AndSomething') camelCaseSeparatedWords asArray => #('FOO' 'Bar1 12' 'And' 'Something')        
     ('FOOBar1 AndSomething') camelCaseSeparatedWords asArray   => #('FOO' 'Bar1 ' 'And' 'Something')       

o  prefixCharactersExactlyMatching: aString
( an extension from the stx:libcompat package )
return the number of characters I share as a prefix with the argument, aString.
This method was originally called charactersExactlyMatching:,
and has been renamed to avoid misinterpretation.

Usage example(s):

     'abc'  prefixCharactersExactlyMatching:'abc'
     'abc'  prefixCharactersExactlyMatching:'abcd'
     'abcd' prefixCharactersExactlyMatching:'abc'
     'abc'  prefixCharactersExactlyMatching:'abd'
     'abc'  prefixCharactersExactlyMatching:'xxx'

o  skipDelimiters: delimiters startingAt: startArg
Answer the index of the character within the receiver, starting at start,
that does NOT match one of the delimiters.
If the receiver does not contain any of the delimiters, answer size + 1.
Assumes the delimiters to be a non-empty string.

Usage example(s):

     '123***7890' skipDelimiters:'*' startingAt:4    
     '123***7890' skipDelimiters:'*' startingAt:3    
     '123***7890' skipDelimiters:'*' startingAt:10   
     '123*******' skipDelimiters:'*' startingAt:10   

o  substrings
return a collection consisting of all words contained in the receiver.
Words are separated by whitespace.
This has been added for Squeak compatibility.
(sigh: it is called #'subStrings' in V'Age, and #'asCollectionOfWords' in ST/X)

Usage example(s):

     'foo bar baz' substrings

o  substringsSeparatedBy: separatorCharacter
return a collection consisting of all words contained in the receiver.
Words are separated by the given separator character.
This has been added for Squeak/Pharo compatibility.
(sigh: it is called #'subStrings:' in V'Age,
and #'asCollectionOfSubstringsSeparatedBy' in ST/X)

Usage example(s):

     'foo bar, baz' substringsSeparatedBy:$,
     '1.2.3.4' substringsSeparatedBy:$.

o  translated
( an extension from the stx:libcompat package )
Dummy - Added for Squeak/Pharo compatibility

o  trimBoth
return a copy of the receiver without leading and trailing whiteSpace.
Added for Squeak compatibility (an alias for withoutSeparators)

o  unescapePercents
( an extension from the stx:libcompat package )
decode %xx form. This is the opposite of #encodeForHTTP

o  unescapePercentsWithTextEncoding: encodingName
( an extension from the stx:libcompat package )
decode string including %XX form

o  urlDecoded
( an extension from the stx:libbasic2 package )
decode %xx form. This is the opposite of #urlEncoded

Usage example(s):

     'abc%61def' unescapePercents
     'abc%61def' urlDecoded
     
      (HTMLUtilities urlEncoded:'_-.*Frankfurt(Main) Hbf') unescapePercents
      (HTMLUtilities urlEncoded:'_-.*Frankfurt(Main) Hbf') urlDecoded

      (HTMLUtilities urlEncoded:'-_.*%exept ex+pecco;') unescapePercents
      (HTMLUtilities urlEncoded:'-_.*%exept+ex+pecco;') urlDecoded

o  urlEncoded
( an extension from the stx:libbasic2 package )
encode into %xx form. This is the opposite of #urlDecoded

Usage example(s):

     'abcäöüdef' urlEncoded urlDecoded
     'abc%def' urlEncoded urlDecoded
     'abc def' urlEncoded urlDecoded
     
      ('_-.*Frankfurt(Main) Hbf' urlEncoded) unescapePercents
      ('_-.*Frankfurt(Main) Hbf' urlEncoded) urlDecoded

      ('-_.*%exept ex+pecco;' urlEncoded) unescapePercents
      ('-_.*%exept+ex+pecco;' urlEncoded) urlDecoded

o  withBlanksTrimmed
Return a copy of the receiver from which leading and trailing whitespace have been trimmed.
Notice the bad naming - it is trimming separators, not just blanks.
Added for Squeak compatibility and an alias for withoutSeparators

Usage example(s):

     '  hello    world    ' withBlanksTrimmed

o  withNoLineLongerThan: aNumber
( an extension from the stx:libcompat package )
Answer a string with the same content as receiver,
but rewrapped so that no line has more characters than the given number

Usage example(s):

     #(5 7 20) collect:
        [:i | 'Fred the bear went down to the brook to read his book in silence' withNoLineLongerThan: i]

o  withSqueakLineEndings
( an extension from the stx:libcompat package )
assume the string is textual, and that CR, LF, and CRLF are all
valid line endings.
Replace each occurrence with a single line end character.
Notice; that ST/X uses LF as line end internally

o  withoutLeading: char
return a copy of myself without leading a char.
Returns an empty string, if the receiver consist only of a char.

Usage example(s):

     '****foo****' withoutLeading: $*
     'foo****'     withoutLeading: $*
     '*'           withoutLeading: $*
     ''            withoutLeading: $*
     '****foo'     withoutLeading: $*
     '*******'     withoutLeading: $*
     'foo'         withoutLeading: $*
     'f***o***o'   withoutLeading: $*
     ('**' , Character tab asString , '*foo***') withoutLeading: $* inspect

o  withoutTrailing: char
return a copy of myself without trailing char.
Returns an empty string, if the receiver consist only of char.

Usage example(s):

     '    foo....' withoutTrailing:$.
     'foo....'     withoutTrailing:$.
     '    foo'     withoutTrailing:$.
     '.......'     withoutTrailing:$.
     'foo'         withoutTrailing:$.

Compatibility-V'Age
o  addLineDelimiter
( an extension from the stx:libcompat package )
replace all '\'-characters by line delimiter (cr) - characters.
This has been added for VisualAge compatibility.

o  bindWith: aString
return a copy of the receiver, where a '%1' escape is
replaced by aString.
This has been added for VisualAge compatibility.

Usage example(s):

     'do you like %1 ?' bindWith:'smalltalk'
     'do you like %(foo) ?' bindWithArguments:(Dictionary new at:'foo' put:'smalltalk'; yourself)

o  bindWith: string1 with: string2
return a copy of the receiver, where a '%1' escape is
replaced by string1 and '%2' is replaced by string2.
This has been added for VisualAge compatibility.

Usage example(s):

     'do you prefer %1 or rather %2 ?'
        bindWith:'smalltalk' with:'c++'

o  bindWith: 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.
This has been added for VisualAge compatibility.

Usage example(s):

     'do you prefer %1 or rather %2 (not talking about %3) ?'
        bindWith:'smalltalk' with:'c++' with:'c'

o  bindWith: 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.
This has been added for VisualAge compatibility.

Usage example(s):

     'do you prefer %1 or rather %2 (not talking about %3 or even %4) ?'
        bindWith:'smalltalk' with:'c++' with:'c' with:'assembler'

o  bindWith: 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.
This has been added for VisualAge compatibility.

o  bindWith: 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.
This has been added for VisualAge compatibility.

o  bindWith: 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.
This has been added for VisualAge compatibility.

o  bindWith: 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.
This has been added for VisualAge compatibility.

o  bindWith: 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.
This has been added for VisualAge compatibility.

o  bindWithArguments: argumentsCollection
return a copy of the receiver, where a '%i' escape
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.

Usage example(s):

     'do you prefer %1 or rather %2 (not talking about %3) ?'
        bindWithArguments:#('smalltalk' 'c++' 'c')

     'do you %(what) ?'
        bindWithArguments:(Dictionary new at:#'what' put:'understand'; yourself)

o  subStrings
( an extension from the stx:libcompat package )
return a collection consisting of all words contained in the receiver.
Words are separated by whitespace.
This has been added for VisualAge compatibility.
(sigh: it is called #'subbtrings' in Squeak, and #'asCollectionOfWords' in ST/X)

Usage example(s):

     'hello world, this is smalltalk' subStrings

o  subStrings: separatorCharacterOrString
return a collection consisting of all words contained in the receiver.
Words are separated by separatorCharacterOrString.
This is similar to split: (squeak) and asCollectionOfSubstringsSeparatedBy: (st/x)
and has been added for VisualAge compatibility.

Usage example(s):

     'foo:bar:baz:smalltalk' subStrings:$:
     'foo:bar:baz:smalltalk' subStrings:':'
     'foo.bar,baz-smalltalk' subStrings:'.,-'

o  trimSeparators
return a copy of the receiver without leading and trailing whiteSpace.
Added for VisualAge compatibility (an alias for withoutSeparators)

o  with: aString
return a copy of the receiver, where a '%1' escape is replaced by aString.
Added for protocol compatibility with resourcePack xlation.

Usage example(s):

     'do you like %1 ?' with:'smalltalk'
     'do you like %(foo) ?' withArguments:(Dictionary new at:'foo' put:'smalltalk'; yourself)

o  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.

Usage example(s):

     'do you prefer %1 or rather %2 ?' with:'smalltalk' with:'c++'

o  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.

Usage example(s):

     'do you prefer %1 or rather %2 (not talking about %3) ?'
        with:'smalltalk' with:'c++' with:'c'

o  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.

Usage example(s):

     'do you prefer %1 or rather %2 (not talking about %3 or even %4) ?'
        with:'smalltalk' with:'c++' with:'c' with:'assembler'

o  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.

o  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.

o  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.

o  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.

o  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.

o  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.

Usage example(s):

     '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)

Compatibility-VW
o  asComposedText
( an extension from the stx:libcompat package )
ST-80 compatibility
- ST/X does not (as today) support composedTexts.

o  asLogicalFileSpecification
( an extension from the stx:libcompat package )

o  asQualifiedReference
( an extension from the stx:libcompat package )

o  expandMacros
ST80 compatibility - expand '<..>' macros with
argument strings. Similar to #bindWith:.
Read the comment in #expandMacrosWithArguments: about
limited compatibility issues.

Usage example(s):

     'hellofoo' expandMacros

o  expandMacrosWith: arg
ST80 compatibility - expand '<..>' macros with
argument strings. Similar to #bindWith:.
Read the comment in #expandMacrosWithArguments: about
limited compatibility issues.

o  expandMacrosWith: arg1 with: arg2
ST80 compatibility - expand '<..>' macros with
argument strings. Similar to #bindWith:.
Read the comment in #expandMacrosWithArguments: about
limited compatibility issues.

o  expandMacrosWith: arg1 with: arg2 with: arg3
ST80 compatibility - expand '<..>' macros with
argument strings. Similar to #bindWith:.
Read the comment in #expandMacrosWithArguments: about
limited compatibility issues.

o  expandMacrosWith: arg1 with: arg2 with: arg3 with: arg4
ST80 compatibility - expand '<..>' macros with
argument strings. Similar to #bindWith:.
Read the comment in #expandMacrosWithArguments: about
limited compatibility issues.

o  expandMacrosWithArguments: argArray
ST80 compatibility - expand '<..>' macros with
argument strings. Similar to #bindWith:.
WARNING: possibly not all ST80 expansions are supported here.

o  isCharacters
true, if the receiver is a string-like thing.
added for visual works compatibility

JavaScript support
o  charAt0: index
( an extension from the stx:libjavascript package )
returns the n'th character, using a 0-based indexing scheme (sigh)

o  charAt1: index
( an extension from the stx:libjavascript package )
returns the n'th character, using a 1-based indexing scheme (sigh)

o  charCodeAt0: index
( an extension from the stx:libjavascript package )
returns the code of the n'th character, using a 0-based indexing scheme (sigh)

o  charCodeAt1: index
( an extension from the stx:libjavascript package )
returns the code of the n'th character, using a 1-based indexing scheme (sigh)

o  indexOf0: aCharacter
( an extension from the stx:libjavascript package )
returns the index of aCharacter, using a 0-based indexing scheme; -1 if not found (sigh)

o  indexOf1: aCharacter
( an extension from the stx:libjavascript package )
returns the index of aCharacter, using a 1-based indexing scheme; 0 if not found (sigh)

o  js_add: something
( an extension from the stx:libjavascript package )
For JavaScript only:
Generated for +-operator in javascript.

o  js_addFromNumber: aNumber
( an extension from the stx:libjavascript package )
For JavaScript only:
Generated for +-operator in javascript.

o  js_addFromString: aString
( an extension from the stx:libjavascript package )
For JavaScript only:
Generated for +-operator in javascript.

o  js_addFromTime: aTime
( an extension from the stx:libjavascript package )
For JavaScript only:
Generated for +-operator in javascript.

o  js_indexOf: aCharacterOrSubstring
( an extension from the stx:libjavascript package )
JS: collection.indexOf(character)
JS: collection.indexOf(substring)
returns the index of anElement/substring, using a 0-based indexing scheme; -1 if not found (sigh).
Selector-xlation to allow redefinition in CharacterArray, which supports substring searching.

o  js_indexOf: aCharacterOrSubstring _: startIndex
( an extension from the stx:libjavascript package )
JS: collection.indexOf(character, startIndex)
JS: collection.indexOf(substring, startIndex)
returns the index of anElement, using a 0-based indexing scheme; -1 if not found (sigh).
Selector-xlation to allow redefinition in CharacterArray, which supports substring searching.

o  js_lastIndexOf: aCharacterOrSubstring
( an extension from the stx:libjavascript package )
JS: collection.lastIndexOf(character)
JS: collection.lastIndexOf(substring)
returns the index of the last occurrence of anElement/substring, using a 0-based indexing scheme; -1 if not found (sigh).
Selector-xlation to allow redefinition in CharacterArray, which supports substring searching.

o  js_lastIndexOf: aCharacterOrSubstring _: startIndex
( an extension from the stx:libjavascript package )
JS: collection.lastIndexOf(character, startIndex)
JS: collection.lastIndexOf(substring, startIndex)
returns the index of the last occurrence of anElement/substring, using a 0-based indexing scheme; -1 if not found (sigh).
Selector-xlation to allow redefinition in CharacterArray, which supports substring searching.

o  js_split: separator
( an extension from the stx:libjavascript package )
JavaScript: splits the receiver into an array of substrings

o  js_typeof
( an extension from the stx:libjavascript package )
return a string describing what I am

o  lastIndexOf0: aCharacter
( an extension from the stx:libjavascript package )
returns the last index of aCharacter, using a 0-based indexing scheme; -1 if not found (sigh)

o  lastIndexOf1: aCharacter
( an extension from the stx:libjavascript package )
returns the last index of aCharacter, using a 1-based indexing scheme; 0 if not found (sigh)

o  quote
( an extension from the stx:libjavascript package )
wraps the receiver into quotes.
This is the JavaScript standard quote function.

Usage example(s):

     JavaScriptParser evaluate:'''hello''.quote()'     

o  substr0: index
( an extension from the stx:libjavascript package )
extracts a rest-substring, using a 0-based indexing scheme (sigh)

o  substr0: index _: count
( an extension from the stx:libjavascript package )
extracts a substring, using a 0-based indexing scheme (sigh)

o  substr1: index
( an extension from the stx:libjavascript package )
extracts a rest-substring, using a 1-based indexing scheme (sigh)

o  substr1: index _: count
( an extension from the stx:libjavascript package )
extracts a substring, using a 1-based indexing scheme (sigh)

o  substring0: index1
( an extension from the stx:libjavascript package )
extracts a substring, using a 0-based indexing scheme (sigh)

o  substring0: index1 _: index2
( an extension from the stx:libjavascript package )
extracts a substring, using a 0-based indexing scheme (sigh)

o  substring1: index1
( an extension from the stx:libjavascript package )
extracts a substring, using a 1-based indexing scheme (sigh)

o  substring1: index1 _: index2
( an extension from the stx:libjavascript package )
extracts a substring, using a 1-based indexing scheme (sigh)

o  toLowerCase
( an extension from the stx:libjavascript package )
returns a copy of the receiver with all chars in lower case

Usage example(s):

     JavaScriptParser
	evaluate:'''HeLLo''.toLowerCase'

o  toUpperCase
( an extension from the stx:libjavascript package )
returns a copy of the receiver with all chars in upper case

Usage example(s):

     JavaScriptParser
	evaluate:'''HeLLo''.toUpperCase'

o  trim
( an extension from the stx:libjavascript package )
returns a copy of the receiver with all leading and trailing whiteSpace removed

Usage example(s):

     JavaScriptParser
	evaluate:'''    He LLo   ''.trim'

o  trimLeft
( an extension from the stx:libjavascript package )
returns a copy of the receiver with all leading whiteSpace removed

Usage example(s):

     JavaScriptParser
	evaluate:'''    HeLLo   ''.trimLeft'

o  trimRight
( an extension from the stx:libjavascript package )
returns a copy of the receiver with all trailing whiteSpace removed

Usage example(s):

     JavaScriptParser
	evaluate:'''    HeLLo   ''.trimRight'

o  unquote
removes double quotes at begin and end from the receiver (but only if matching).
This is the JavaScript standard unquote function.

o  unquote: quoteCharacter
removes quoteCharacter (if present and matching) from either end of the receiver.

Usage example(s):

     '*hello*' unquote:$*

character searching
o  includesMatchCharacters
return true if the receiver includes any GLOB meta-match characters (i.e. $* or $#)
for match operations; false if not.
Here, do not care for $\ escapes

Usage example(s):

     '*foo' includesMatchCharacters
     '\*foo' includesMatchCharacters
     '\*foo' includesUnescapedMatchCharacters
     '*foo' includesMatchCharacters
     '\\*foo' includesMatchCharacters
     'foo*' includesMatchCharacters
     'foo\*' includesMatchCharacters
     'foo\' includesMatchCharacters

o  includesSeparator
return true, if the receiver contains any whitespace characters

Usage example(s):

     'hello world' includesSeparator
     'helloworld' includesSeparator

o  includesUnescapedMatchCharacters
return true if the receiver really includes any meta characters (i.e. $* or $#)
for match operations; false if not.
Here, care for $\ escapes

Usage example(s):

     '*foo' includesUnescapedMatchCharacters
     '\*foo' includesUnescapedMatchCharacters
     '\\foo' includesUnescapedMatchCharacters
     '\\\$foo' includesUnescapedMatchCharacters
     '*foo' includesUnescapedMatchCharacters
     '\\*foo' includesUnescapedMatchCharacters
     'foo*' includesUnescapedMatchCharacters
     'foo\*' includesUnescapedMatchCharacters
     'foo\' includesUnescapedMatchCharacters

o  indexOfControlCharacterStartingAt: startIndex
return the index of the next control character;
that is a character with asciiValue < 32.
Start the search at startIndex, searching forward.
Return 0 if none is found.

Usage example(s):

     'hello world' asTwoByteString            indexOfControlCharacterStartingAt:1
     'hello world\foo' withCRsasTwoByteString indexOfControlCharacterStartingAt:1

o  indexOfNonDigitStartingAt: startIndex
return the index of the next non-digit character,
starting the search at startIndex, searching forward;
return 0 if no non-digit was found

Usage example(s):

     'hello world' indexOfNonDigitStartingAt:1      => 1
     '    hello world' indexOfNonDigitStartingAt:1  => 1
     '    hello world' indexOfNonDigitStartingAt:1  => 1
     '123    ' indexOfNonDigitStartingAt:1          => 4
     'a   ' indexOfNonDigitStartingAt:1             => 1  
     'a   ' indexOfNonDigitStartingAt:2             => 2  
     '123' indexOfNonDigitStartingAt:1              => 0  
     '123' indexOfNonDigitStartingAt:2              => 0 

     'hello world' asUnicode16String indexOfNonDigitStartingAt:1      => 1
     '    hello world' asUnicode16String indexOfNonDigitStartingAt:1  => 1
     '    hello world' asUnicode16String indexOfNonDigitStartingAt:1  => 1
     '123    ' asUnicode16String indexOfNonDigitStartingAt:1          => 4
     'a   ' asUnicode16String indexOfNonDigitStartingAt:1             => 1  
     'a   ' asUnicode16String indexOfNonDigitStartingAt:2             => 2  
     '123' asUnicode16String indexOfNonDigitStartingAt:1              => 0  
     '123' asUnicode16String indexOfNonDigitStartingAt:2              => 0 

o  indexOfNonSeparator
return the index of the first non-whitespace character.
return 0 if no non-separator was found

Usage example(s):

     '    hello world' indexOfNonSeparator
     '    ' indexOfNonSeparator
     'a   ' indexOfNonSeparator
     'abc' indexOfNonSeparator
     ' ' indexOfNonSeparator
     '' indexOfNonSeparator

o  indexOfNonSeparatorStartingAt: startIndex
return the index of the next non-whitespace character,
starting the search at startIndex, searching forward;
return 0 if no non-separator was found

Usage example(s):

     '    hello world' indexOfNonSeparatorStartingAt:1
     '    ' indexOfNonSeparatorStartingAt:1
     'a   ' indexOfNonSeparatorStartingAt:2

Usage example(s):

     |s index1 index2|
     s := '   foo    bar      baz'.
     index1 := s indexOfNonSeparatorStartingAt:1.
     index2 := s indexOfSeparatorStartingAt:index1.
     s copyFrom:index1 to:index2 - 1

o  indexOfSeparator
return the index of the first whitespace character;
starting the search at the beginning, searching forward;
return 0 if no separator was found

Usage example(s):

     'hello world' indexOfSeparator
     'helloworld' indexOfSeparator
     'hello   ' indexOfSeparator
     '   hello' indexOfSeparator

o  indexOfSeparatorOrEndStartingAt: startIndex
return the index of the next whitespace character,
starting the search at startIndex, searching forward;
return the index of one beyond the end of the receiver if no separator was found.
To extract the word, copy from startIndex to the returned index-1

Usage example(s):

     'hello world' indexOfSeparatorOrEndStartingAt:3
     ' hello world' indexOfSeparatorOrEndStartingAt:3
     'hello world ' indexOfSeparatorOrEndStartingAt:3
     'hello world ' indexOfSeparatorOrEndStartingAt:6
     'hello world ' indexOfSeparatorOrEndStartingAt:7
     'helloworld ' indexOfSeparatorOrEndStartingAt:7
     'helloworld' indexOfSeparatorOrEndStartingAt:7
     'helloworld' indexOfSeparatorStartingAt:7

o  indexOfSeparatorStartingAt: startIndex
return the index of the next whitespace character,
starting the search at startIndex, searching forward;
return 0 if no separator was found

Usage example(s):

     'hello world' indexOfSeparatorStartingAt:3
     ' hello world' indexOfSeparatorStartingAt:3
     'hello world ' indexOfSeparatorStartingAt:3
     'hello world ' indexOfSeparatorStartingAt:6
     'hello world ' indexOfSeparatorStartingAt:7
     'helloworld ' indexOfSeparatorStartingAt:7
     'helloworld' indexOfSeparatorStartingAt:7

o  isValidMatchPattern
return true if the receiver consists of a valid GLOB match pattern

Usage example(s):

        '[' isValidMatchPattern -> false
        '[]' isValidMatchPattern -> true

o  lastIndexOfSeparator
return the last index of a whitespace character (space or tab).
(i.e. start the search at the end and search backwards);
Returns 0 if no separator is found.

Usage example(s):

     'hello world' lastIndexOfSeparator
     'helloworld' lastIndexOfSeparator
     'hel lo wor ld' lastIndexOfSeparator
     'hel   ' lastIndexOfSeparator 6

o  lastIndexOfSeparatorStartingAt: startIndex
return the index of the previous whitespace character,
starting the search at startIndex (and searching backwards);
returns 0 if no separator was found

Usage example(s):

     'hello world' lastIndexOfSeparatorStartingAt:3
     'hello world' lastIndexOfSeparatorStartingAt:7
     'helloworld' lastIndexOfSeparatorStartingAt:7
     ' helloworld' lastIndexOfSeparatorStartingAt:7

comparing
o  < aString
Compare the receiver with the argument and return true if the
receiver is less than the argument. Otherwise return false.
This comparison is based on the elements ascii code -
i.e. upper/lowercase & upper/lowercase & national characters are NOT treated specially.

o  <% aString
alias of #compareNaturalWith: answering true if a receiver is less than aString.

o  <= aString
Compare the receiver with the argument and return true if the
receiver is less than or equal the argument. Otherwise return false.
This comparison is based on the elements ascii code -
i.e. upper/lowercase & upper/lowercase & national characters are NOT treated specially.

Usage example(s):

        '123456789' asUnicodeString <= '123456789' asUnicodeString
        '123456780' asUnicodeString <= '123456789' asUnicodeString
        '12345' asUnicodeString <= '123456780' asUnicodeString
        '123456789' asUnicodeString <= '12345' asUnicodeString
        '123456789' asUnicodeString <= '123456780' asUnicodeString

o  = aString
Compare the receiver with the argument and return true if the
receiver is equal to the argument. Otherwise return false.

This compare does NOT ignore case differences,
therefore 'foo' = 'Foo' will return false.
Since this is incompatible to ST-80 (at least, V2.x) , this may change.

Usage example(s):

     'foo' = 'Foo'
     'foo' = 'bar'
     'foo' = 'foo'
     'foo' = 'foo' asText
     'foo' asText = 'foo'
     'foo' asText = 'foo' asText

o  > aString
Compare the receiver with the argument and return true if the
receiver is greater than the argument. Otherwise return false.
This comparison is based on the elements ascii code -
i.e. upper/lowercase & upper/lowercase & national characters are NOT treated specially.

o  after: aString
Compare the receiver with the argument and return true if the
receiver should come after the argument in a sorted list.
Otherwise return false.
NOTE: The comparison should be language specific, depending on the value of
LC_COLLATE, which is initialized from the environment.

Currently it is for Strings, but not for UnicodeStrings...

STUPID:
#after has a completely different meaning in SeqColl...
... therefore it is marked as obsolete.


** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  caselessAfter: aString
True if the receiver comes after aString, if compared caseless.
(i.e. if receiver > aString, ignoring case)

Usage example(s):

     'aaa1' > 'aaA2' -> true
     'aaa1' caselessAfter: 'aaA2' -> false

o  caselessBefore: aString
True if the receiver comes before aString, if compared caseless.
(i.e. if receiver < aString, ignoring case)

Usage example(s):

     'aaa1' < 'aaA2' -> false
     'aaa1' caselessBefore: 'aaA2' -> true

o  caselessEqual: aString
True if the receiver has the same characters as aString, if compared caseless.
(i.e. if receiver = aString, ignoring case)

Usage example(s):

     'aaa1' = 'aaA1' -> false
     'aaa1' caselessEqual: 'aaA1' -> true

o  compareAsVersionNumberWith: aStringOrCollection
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.
Compare as version numbers in the form a.b.c... .

Usage example(s):

     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.
     self assert:('1.1' compareAsVersionNumberWith:'1.2') < 0.
     self assert:('1.10' compareAsVersionNumberWith:'1.2') > 0.
     self assert:('1.2.3.4' compareAsVersionNumberWith:'1.2.3.5') < 0.
     self assert:('1.2.3.4' compareAsVersionNumberWith:'1.2.3.3') > 0.
     self assert:('1.2.3.4' compareAsVersionNumberWith:'1.2.3') > 0.
     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.

o  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.

This comparison is based on the elements ascii code -
i.e. national characters are NOT treated specially.
'foo' compareWith: 'Foo' will return 0

Usage example(s):

     'aaa1' < 'aaA2' -> false
     'aaa1' compareCaselessWith: 'aaA2' -> -1

o  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.
The comparison is language specific, depending on the value of
LC_COLLATE, which is in the shell environment.

o  compareNaturalWith: aString
Compare the receiver with the argument.
Do a natural compare, treating numbers like humans would:
so 'a3' is less than 'a22'.
Return 1 if the receiver is greater, 0 if equal and -1 if less than the argument.
This comparison is based on the elements' codepoints
i.e. upper/lowercase & national characters are NOT treated specially.

Usage example(s):

^ s compareNaturalWith:aString string.

Usage example(s):

        'a11' compareNaturalWith:'a2'
        'a11' compareNaturalWith:'a11'
        'a222abcdef' compareNaturalWith:'a33abcd'
        'a22zz' compareNaturalWith:'a22zz'
        'abcdef' compareNaturalWith:'abcde'
        'abcde44' compareNaturalWith:'abcde'
        'abcde' compareNaturalWith:'abcde44'
        'abc2.0.0' compareNaturalWith:'abc20.1.0'
        'abc20.00.0' compareNaturalWith:'abc20.1.0'
        '123456789012345678901234567890' compareNaturalWith:'123456789012345678901234567899'

o  compareWith: 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.
This comparison is based on the elements' codepoints -
i.e. upper/lowercase & national characters are NOT treated specially.
'foo' compareWith: 'Foo' will return 1.
while 'foo' sameAs:'Foo' will return true

o  endsWith: aStringOrCharacter
return true, if the receiver ends with something, aStringOrCharacter.
If aStringOrCharacter is empty, true is returned

Usage example(s):

     '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:''
     'hello' endsWith:'hello'
     '' endsWith:'hello'
     '' endsWith:$a
     '' endsWith:1234
     'a' endsWith:1234 

o  endsWith: aStringOrCharacter caseSensitive: caseSensitive
return true, if the receiver ends with something, aStringOrCharacter.
If aStringOrCharacter is empty, true is returned

Usage example(s):

     'hello World' endsWith:'world' caseSensitive:true
     'hello World' endsWith:'world' caseSensitive:false
     '' endsWith:'' caseSensitive:true

o  endsWithDigit
Answer whether the receiver's final character represents a digit. 3/11/96 sw

Usage example(s):

     'hello' endsWithDigit
     '12hello' endsWithDigit
     'hello12' endsWithDigit

o  hammingDistanceTo: aString
return the hamming distance (the number of characters which are different).
In information theory, the Hamming distance between two strings of equal length
is the number of positions for which the corresponding symbols are different.
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.

Usage example(s):

     'roses' hammingDistanceTo:'toned'
     'roses' hammingDistanceTo:'doses'

o  hash
return an integer useful as a hash-key

Usage example(s):

whenever changing, also care for String>>hash.

Usage example(s):

Set allSubInstancesDo:[:s | s rehash]

Usage example(s):

     'a' hash
     'a' asUnicode16String hash
     'a' asUnicode32String hash
     'aa' hash
     'aa' asUnicode16String hash
     'aa' asUnicode32String hash
     'ab' hash
     'ab' asUnicode16String hash
     'ab' asUnicode32String hash
     'ab' hash
     'ab' asArray hash

Usage example(s):

        |syms ms|

        syms := Symbol allInstances.
        Transcript show:'syms: '; showCR:syms size.
        Transcript show:'sdbm hashes: '; showCR:(syms collect:[:s| s hash]) asSet size.
        Transcript show:'dragonBook hashes: '; showCR:(syms collect:[:s| s hash_dragonBook]) asSet size.

        ms := Time millisecondsToRun:[
            10 timesRepeat:[
                syms do:[:each| each hash].
            ].
        ].
        Transcript show:'sdbm hash: '; showCR:ms.

        ms := Time millisecondsToRun:[
            10 timesRepeat:[
                syms do:[:each| each hash_dragonBook].
            ].
        ].
        Transcript show:'dragonBook: '; showCR:ms.

        syms := syms collect:[:each| each asUnicode16String].
        ms := Time millisecondsToRun:[
            10 timesRepeat:[
                syms do:[:each| each hash].
            ].
        ].
        Transcript show:'unicode sdbm hash: '; showCR:ms.

        ms := Time millisecondsToRun:[
            10 timesRepeat:[
                syms do:[:each| each hash_dragonBook].
            ].
        ].
        Transcript show:'unicode dragonBook:'; showCR:ms.

o  hash_dragonBook
return an integer useful as a hash-key

o  hash_fnv1a
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)

Usage example(s):

     'abc' hash_fnv1a
     'abc' asUnicode16String hash_fnv1a
     'abc' asUnicode32String hash_fnv1a

     'foofooHelloWorld' hash_fnv1a
     'foofooHelloWorld' asUnicode16String hash_fnv1a
     'foofooHelloWorld' asUnicode32String hash_fnv1a

     'blablaHelloWorld' hash_fnv1a
     'blablaHelloWorld' asUnicode16String hash_fnv1a
     'blablaHelloWorld' asUnicode32String hash_fnv1a

o  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).

Usage example(s):

     '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

o  hash_java
return an integer useful as a hash-key.
This method uses the same algorithm as used in
the java virtual machine
(which is actually not a very good one).

Usage example(s):

     'abc' hash_java
     'foofooHelloWorld' hash_java
     'blablaHelloWorld' hash_java

o  hash_sdbm
return an integer useful as a hash-key.
This method implements the sdbm algorithm.

o  levenshteinTo: aString
return the levenshtein distance to the argument, aString;
this value corresponds to the number of replacements that have to be
made to get aString from the receiver.
See IEEE transactions on Computers 1976 Pg 172 ff.

Usage example(s):

     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)
        k: keyboard weight (k) (typing a nearby key) - or nil (then use s)
        c: case weight (4)                           - or nil (then use s)
        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

Usage example(s):

     'computer' levenshteinTo:'computer'     => 0
     'Computer' levenshteinTo:'computer'     => 4
     'computer' levenshteinTo:'Computer'     => 4

     'cOmputer' levenshteinTo:'computer'     => 4
     'cOmpuTer' levenshteinTo:'computer'     => 8
     'cimputer' levenshteinTo:'computer'     => 4
     'cumputer' levenshteinTo:'computer'     => 4

     'cmputer' levenshteinTo:'computer'      => 2
     'coomputer' levenshteinTo:'computer'    => 6

     'ocmprt' levenshteinTo:'computer'       => 16
     'ocmputer' levenshteinTo:'computer'     => 8
     'cmputer' levenshteinTo:'computer'      => 2
     'computer' levenshteinTo:'cmputer'      => 6
     'Computer' levenshteinTo:'computer'     => 4

     'compiter' levenshteinTo:'computer'     => 4
     'compoter' levenshteinTo:'computer'     => 4

     'comptuer' levenshteinTo:'computer'     => 8

o  levenshteinTo: aString s: substWeight k: kbdTypoWeight c: caseWeight i: insrtWeight d: deleteWeight
parametrized levenshtein.
return the levenshtein distance to the argument, aString;
this value corrensponds to the number of replacements that have to be
made to get aString from the receiver.
The arguments are the costs for
s:substitution,
k:keyboard type (substitution),
c:case-change,
i:insertion
d:deletion
of a character.
See IEEE transactions on Computers 1976 Pg 172 ff

o  sameAs: aString
Compare the receiver with the argument like =, but ignore case differences.
Return true or false.

Usage example(s):

     'foo' sameAs: 'Foo'
     'foo' sameAs: 'bar'
     'foo' sameAs: 'foo'

o  sameAs: aString caseSensitive: caseSensitive
Compare the receiver with the argument.
If caseSensitive is false, this is the same as #sameAs:,
if false, this is the same as #=.

Usage example(s):

     'foo' sameAs:'Foo' caseSensitive:false
     'foo' sameAs:'foo' caseSensitive:true

o  sameAs: aString ignoreCase: ignoreCase
Compare the receiver with the argument.
If ignoreCase is true, this is the same as #sameAs:,
if false, this is the same as #=.

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  sameCharacters: aString
count & return the number of characters which are the same
(ignoring case and emphasis) in the receiver and the argument, aString.

Usage example(s):

     'foobarbaz' sameCharacters: 'foo'
     'foobarbaz' sameCharacters: 'Foo'
     'foobarbaz' sameCharacters: 'baz'

o  sameEmphasisAs: aStringOrText
compare the receiver's and the argument's emphasis

Usage example(s):

     'hello' asText sameEmphasisAs: 'hello'
     'hello' asText sameEmphasisAs: 'hello' asText
     'hello' asText allBold sameEmphasisAs: 'hello'
     'hello' asText allBold sameEmphasisAs: 'fooba' asText allBold
     'hello' asText allBold sameEmphasisAs: 'fooba' asText allItalic

o  sameStringAndEmphasisAs: aStringOrText
compare both emphasis and string of the receiver and the argument

Usage example(s):

     'hello' asText sameEmphasisAs: 'hello'
     'hello' asText sameEmphasisAs: 'hello' asText
     'hello' asText allBold sameEmphasisAs: 'hello'
     'hello' asText allBold sameEmphasisAs: 'fooba' asText allBold
     'hello' asText allBold sameEmphasisAs: 'fooba' asText allItalic

     'hello' sameEmphasisAs: 'hello' asText
     'hello' sameEmphasisAs: 'hello' asText allBold
     'hello' sameEmphasisAs: 'fooba'
     'hello' sameEmphasisAs: 'fooba' asText
     'hello' sameEmphasisAs: 'fooba' asText allBold
     'hello' sameEmphasisAs: 'fooba' asText allItalic

     'hello' asText sameStringAndEmphasisAs: 'hello'
     'hello' asText sameStringAndEmphasisAs: 'hello' asText
     'hello' asText allBold sameStringAndEmphasisAs: 'hello'
     'hello' asText allBold sameStringAndEmphasisAs: 'fooba' asText allBold
     'hello' asText allBold sameStringAndEmphasisAs: 'fooba' asText allItalic

     'hello' sameStringAndEmphasisAs: 'hello' asText
     'hello' sameStringAndEmphasisAs: 'hello' asText allBold
     'hello' sameStringAndEmphasisAs: 'fooba'
     'hello' sameStringAndEmphasisAs: 'fooba' asText
     'hello' sameStringAndEmphasisAs: 'fooba' asText allBold
     'hello' sameStringAndEmphasisAs: 'fooba' asText allItalic

o  spellAgainst: aString
return an integer between 0 and 100 indicating how similar
the argument is to the receiver. No case conversion is done.
This algorithm is much simpler (but also less exact) than the
levenshtein distance. Experiment which is better for your
application.

Usage example(s):

     'Smalltalk' spellAgainst: 'Smalltlak' => 88
     'Smalltalk' spellAgainst: 'smalltlak' => 77
     'Smalltalk' spellAgainst: 'smalltalk' => 88
     'Smalltalk' spellAgainst: 'smalltlk'  => 77
     'Smalltalk' spellAgainst: 'Smalltolk' => 88
     'Smalltalk' spellAgainst: 'Smalltalk' => 100

o  startsWith: aStringOrCharacter
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.

Usage example(s):

     'abcde' startsWith:#($a $b $c)
     'abcde' startsWith:'abc'
     'abcd' startsWith:'abcde'
     'abcde' startsWith:'abd'
     'hello world' startsWith:'hello'
     'hello world' asText allBold startsWith:'hello'
     'hello world' asText allBold startsWith:''

o  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.

Usage example(s):

     'aBCde' startsWith:'abc' caseSensitive:true
     'aBCde' startsWith:'abc' caseSensitive:false

o  startsWithAnyOf: aCollectionOfStrings caseSensitive: caseSensitive
return true, if the receiver starts with any in aCollectionOfStrings, possibly ignoring case differences.

Usage example(s):

     'abcde' startsWithAnyOf:#('AB' 'xx') caseSensitive:true  => false
     'abcde' startsWithAnyOf:#('AB' 'xx') caseSensitive:false => true
     'abcde' startsWithAnyOf:#('AC' 'ac') caseSensitive:false => false

o  startsWithDigit
Answer whether the receiver's first character represents a digit. 3/11/96 sw

Usage example(s):

     'hello' startsWithDigit
     '12hello' startsWithDigit
     'hello12' startsWithDigit

o  startsWithSeparator
Answer whether the receiver's first character is whitespace

Usage example(s):

     'hello' startsWithSeparator 
     ' 12hello' startsWithSeparator    
     (Character tab,'hello12') startsWithSeparator  

converting
o  asAsciiZ
if the receiver does not end with a 0-valued character, return a copy of it,
with an additional 0-character. Otherwise return the receiver. This is sometimes
needed when a string has to be passed to C, which needs 0-terminated strings.
Notice, that all singleByte strings are already 0-terminated in ST/X, whereas wide
strings are not.

Usage example(s):

     'abc' asAsciiZ
     'abc' asUnicode16String asAsciiZ

o  asByteArray
depending on the size of the characters in the receiver,
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.
Attention: The bytes are in native byte order.
Caveat: better use utf8Encoded, to get reproducible results

o  asByteArrayMSB: msb
depending on the size of the characters in the receiver,
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 reproducible results.
Caveat: when swapping, this seems to work with twoByte chars only.

o  asCanonicalizedFilename
return a Filename with pathname taken from the receiver.
The filename is canonicalized, meaning that it cares for trailing directory separators,
'.' components etc.

Usage example(s):

on windows:
     'c:\foo\bar' asFilename                        => PCFilename('c:\foo\bar')
     'c:\foo\bar\' asFilename                       => PCFilename('c:\foo\bar\')
     'c:\foo\bar\..\baz' asFilename                 => PCFilename('c:\foo\bar\..\baz')
     'c:\foo\bar\..\baz\.' asFilename               => PCFilename('c:\foo\bar\..\baz\.')
     'c:\foo\bar' asCanonicalizedFilename           => PCFilename('c:\foo\bar')
     'c:\foo\bar\' asCanonicalizedFilename          => PCFilename('c:\foo\bar')
     'c:\foo\bar\..\baz' asCanonicalizedFilename    => PCFilename('c:\foo\baz')
     'c:\foo\bar\..\baz\.' asCanonicalizedFilename  => PCFilename('c:\foo\baz')
    
    on unix:
     '/foo/bar' asFilename                          => UnixFilename('/foo/bar')
     '/foo/bar/' asFilename                         => UnixFilename('/foo/bar/')
     '/foo/bar/../baz' asFilename                   => UnixFilename('/foo/bar/../baz')
     '/foo/bar/../baz/.' asFilename                 => UnixFilename('/foo/bar/../baz/.') 
     '/foo/bar' asCanonicalizedFilename             => UnixFilename('/foo/bar') 
     '/foo/bar/' asCanonicalizedFilename            => UnixFilename('/foo/bar') 
     '/foo/bar/../baz' asCanonicalizedFilename      => UnixFilename('/foo/baz') 
     '/foo/bar/../baz/.' asCanonicalizedFilename    => UnixFilename('/foo/baz')

    on any:
     '/foo/bar/../baz/.' asUnixFilename asCanonicalizedFilename => UnixFilename('/foo/baz')

o  asClassIfAbsent: exceptionValue
return the class named after me.
Conceptionally the same as
Smalltalk classNamed:self asSymbol ifNil:exceptionValue
or:
self asSymbol asClassIfAbsent:exceptionValue
but avoids the creation of symbols for unknown classes

Usage example(s):

     'Array' asClassIfAbsent:123
     'Foo' asClassIfAbsent:123

o  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.
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
this method and we did not want to risk any incompatibilities)

Usage example(s):

     '1 one\2 two\3 three\4 four\5 five' withCRs asCollectionOfLines
     '1 one\\\\2 two\3 three' withCRs asCollectionOfLines

     ('foo \r\nbar\nbaz\t\r\n\r\nbla' printf:#())
        asCollectionOfLines collect:[:l | (l endsWith:Character return) ifTrue:[l copyButLast:1] ifFalse:l]

o  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.

Usage example(s):

     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

o  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.

Usage example(s):

     '1\2\3' withCRs asCollectionOfLines
     '1\2\3\' withCRs asCollectionOfLines
     '1\2\3' withCRs asCollectionOfLinesWithReturn
     '1\2\3\' withCRs asCollectionOfLinesWithReturn
     '' withCRs asCollectionOfLinesWithReturn

o  asCollectionOfSubstringsSeparatedBy: aCharacter
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 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.

Usage example(s):

     '1 one:2 two:3 three:4 four:5 five' asCollectionOfSubstringsSeparatedBy:$:
     '1 one:2 two:3 three:4 four:5 five:' asCollectionOfSubstringsSeparatedBy:$:
     '1 one 2 two 3 three 4 four 5 five' asCollectionOfSubstringsSeparatedBy:Character space

o  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.
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.

Usage example(s):

     'asd''f;d''dd;s' asCollectionOfSubstringsSeparatedBy:$; exceptIn:$'
     'asd''f;d''dd;s' asText asCollectionOfSubstringsSeparatedBy:$; exceptIn:$'

Usage example(s):

'asd "hello bla" foo "bla bla" bar' asCollectionOfSubstringsSeparatedBy:$  exceptIn:$"

o  asCollectionOfSubstringsSeparatedBy: aFieldSeparatorString textSeparator: aTextSeparatorOrNil
return a collection containing the words (separated by aFieldSeparatorString) of the receiver.
Individual words might be enclosed in aTextSeparator characters, in case they contain blanks or fieldSeparators.
Typically used for CSV line parsing, with a $; as aFieldSeparator and $'' (dquote) as textSeparator.

Usage example(s):

     self assert:(('#First#, #Second,SecondAdd#, #Third#' asCollectionOfSubstringsSeparatedBy:',' textSeparator: $#)
                  sameContentsAs:#('First' 'Second,SecondAdd' 'Third')).
     self assert:(('#Fir##st#, #Second,SecondAdd#, #Third#' asCollectionOfSubstringsSeparatedBy:',' textSeparator: $#)
                  sameContentsAs:#('Fir#st' 'Second,SecondAdd' 'Third')).
     self assert:(('#Fir##st#, Second,SecondAdd, #Third#' asCollectionOfSubstringsSeparatedBy:',' textSeparator: $#)
                  sameContentsAs:#('Fir#st' 'Second' 'SecondAdd' 'Third')).
     self assert:(('First,Second,Third,,' asCollectionOfSubstringsSeparatedBy:',' textSeparator:nil)
                   sameContentsAs:#('First' 'Second' 'Third' '' '')).
     self assert:(('First,Second,Third,,' asCollectionOfSubstringsSeparatedBy:',' textSeparator:'#')
                   sameContentsAs:#('First' 'Second' 'Third' '' '')).

o  asCollectionOfSubstringsSeparatedByAll: aSeparatorString
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.

Usage example(s):

     '1::2::3::4::5::' asCollectionOfSubstringsSeparatedByAll:'::'

o  asCollectionOfSubstringsSeparatedByAny: aCollectionOfSeparators
return a collection containing the words (separated by any character
from aCollectionOfSeparators) of the receiver.
This allows breaking up strings using any character as separator.

Usage example(s):

     'hello:world:isnt:this nice' asCollectionOfSubstringsSeparatedByAny:#($:)
     'hello:world:isnt:this nice' asCollectionOfSubstringsSeparatedByAny:':'
     'hello:world:isnt:this nice' asCollectionOfSubstringsSeparatedByAny:(Array with:$: with:Character space)
     'hello:world:isnt:this nice' asCollectionOfSubstringsSeparatedByAny:': '
     'h1e2l3l4o' asCollectionOfSubstringsSeparatedByAny:($1 to: $9)

o  asCollectionOfSubstringsSeparatedByAny: aFieldSeparatorString textSeparator: aTextSeparatorCharOrNil
return a collection containing the words (separated by any character in aFieldSeparatorString) of the receiver.
Individual words might be enclosed in aTextSeparatorCharOrNil characters, in case they contain blanks or fieldSeparators.
Typically used for CSV line parsing, with a ';,' as aFieldSeparator and $'' (dquote) as textSeparator.

Usage example(s):

     self assert:(('#First#, #Second,;SecondAdd#; #Third#' asCollectionOfSubstringsSeparatedByAny:';,' textSeparator: $#)
                  sameContentsAs:#('First' 'Second,;SecondAdd' 'Third')).
     self assert:(('#Fir##st#, #Second,SecondAdd#, #Th;ird#' asCollectionOfSubstringsSeparatedByAny:',;' textSeparator: $#)
                  sameContentsAs:#('Fir#st' 'Second,SecondAdd' 'Th;ird')).
     self assert:(('First,Second,Third,;' asCollectionOfSubstringsSeparatedByAny:',;' textSeparator:nil)
                   sameContentsAs:#('First' 'Second' 'Third' '' '')).
     self assert:(('First,Second,Third,;' asCollectionOfSubstringsSeparatedByAny:';,' textSeparator:'#')
                   sameContentsAs:#('First' 'Second' 'Third' '' '')).

o  asCollectionOfWords
return a collection containing the words (separated by whitespace)
of the receiver. Multiple occurrences of whitespace characters will
be treated like one - i.e. whitespace is skipped.
(sigh: it is called #'subStrings' in V'Age, and #'substrings' in Squeak)

Usage example(s):

     'hello world isnt this nice' asCollectionOfWords
     'hello world isnt this nice' asCollectionOfWordsDo:#transcribeCR
     '    hello    world   isnt   this   nice  ' asCollectionOfWords
     'hello' asCollectionOfWords
     '' asCollectionOfWords
     '      ' asCollectionOfWords
     ' foo bar__baz__bla__ bar ' asCollectionOfWords
     ' foo __bar__baz__bla__ bar ' asCollectionOfWords

o  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).
This is the same as 'asCollectionOfWords do:...' but avoids the creation of
a temporary collection.

Usage example(s):

     '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]

o  asDenseUnicodeString
return the receiver as single-byte, double byte or 4-byte unicode string,
depending on the number of bits required to hold all characters in myself.
Use this to extract non-wide parts from a wide string,
i.e. after a substring has been copied out of a wide string

Usage example(s):

     '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

o  asFilename
return a Filename with pathname taken from the receiver

o  asFixedDecimal
( an extension from the stx:libbasic2 package )
return a fixedDecimal approximating the receiver's value.
Takes the scale which is present in the receiver string

Usage example(s):

     '123.45' asFixedDecimal   -> 123.45
     '123.456' asFixedDecimal  -> 123.456
     '123.4' asFixedDecimal    -> 123.4
     '123.' asFixedDecimal     -> 123
     '123' asFixedDecimal      -> 123

o  asFixedDecimal: scale
( an extension from the stx:libbasic2 package )
return a fixedDecimal approximating the receiver's value
to scale fractional digits

o  asFixedPoint
marked as obsolete by exept MBP at 18-09-2021

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  asFixedPoint: scale
marked as obsolete by exept MBP at 18-09-2021

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  asFloat
read a float number from the receiver.
Notice, that a ConversionError may be raised during the read,
so you better setup some exception handler when using this method.

Usage example(s):

     '0.123' asFloat
     '12345' asFloat
     '(1/5)' asFloat
     'blabla' asFloat
     Object errorSignal handle:[:ex | ex return:0] do:['foo' asFloat]

o  asImmutableCollection
fallback for subclasses of me which are not single byte strings.
return myself

o  asImmutableString
return a write-protected copy of myself.
Redefined in Symbol and ImmutableString to return self.

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  asInteger
convert the receiver into an integer.
Notice, that a ConversionError may be raised during the read,
so you better setup some exception handler when using this method.
Also notice, that this method here is more strict than the code found
in other Smalltalks.
For less strict integer reading, use Integer readFrom:aString

Usage example(s):

     '12345678901234567890' asInteger
     '-1234' asInteger

     The following raises an error:
         '0.123' asInteger              <- reader finds more after reading 0

     whereas the less strict readFrom does not:
         Integer readFrom:'0.123'       <- reader stops at ., returning 0

     '0.123' asInteger
     '0.123' asNumber    <- returns what you expect
     Object errorSignal handle:[:ex | ex return:0] do:['foo' asInteger]

o  asLowercase
return a copy of myself in lowercase letters

Usage example(s):

     'helloworld' asUnicode16String asLowercase
     'HelloWorld' asLowercase
     'HelloWorld' asUnicode16String asLowercase
     'HelloWorld' asLowercaseFirst
     'HelloWorld' asUppercase
     'ĀĂĄĆĈ' allBold asLowercase
     'HelloWorldŸ' asLowercase - currently returns an U16 string; should this be u8?

o  asLowercaseFirst
return a copy of myself where the first character is converted to lowercase.
If the first character is already lowercase, or there is no lowercase for it, return the
receiver.

Usage example(s):

     'HelloWorld' asLowercase
     'HelloWorld' asLowercaseFirst
     'HelloWorld' allBold asLowercaseFirst
      #Object asLowercaseFirst
      #Object allBold asLowercaseFirst

o  asLowercaseLast
return a copy of myself where the last character is
converted to lowercase.

Usage example(s):

     'HelloWorld' asLowercase
     'HelloWorlD' asLowercaseLast
     'HelloWorlD' allBold asLowercaseLast

o  asMimeType
( an extension from the stx:libview2 package )
return myself as a mimeType instance

Usage example(s):

     'text/html' asMimeType isTextType
     'text/html' asMimeType isImage
     'image/gif' asMimeType isImage
     'image/gif' asMimeType asMimeType

o  asNumber
read a number from the receiver.
Notice, that (in contrast to ST-80) a ConversionError may be raised during the read,
so you better setup some signal handler when using this method.
Also notice, that this is meant to read end-user numbers from a string;
it does not handle smalltalk numbers (i.e. radix).
To read a smalltalk number, use Number >> readSmalltalkFrom:.
This may change if ANSI specifies it.

Usage example(s):

     '123'     asNumber
     '123.567' asNumber
     '(5/6)'   asNumber
     'foo'     asNumber
     '123a'    asNumber
     Object errorSignal handle:[:ex | ex returnWith:0] do:['foo' asNumber]

o  asNumberFromFormatString: ignored
read a number from the receiver, ignoring any nonDigit characters.
This is typically used to convert from strings which include
dollar-signs or millenium digits. However, this method also ignores
the decimal point (if any) and therefore should be used with care.
CAVEAT: this is a dummy fallback implementation for compatibility

Usage example(s):

     'USD 123' asNumberFromFormatString:'foo'
     'DM 123'  asNumberFromFormatString:'foo'
     '123'     asNumberFromFormatString:'foo'
     '123.567' asNumberFromFormatString:'foo'
     '(5/6)'   asNumberFromFormatString:'foo'
     'foo'     asNumberFromFormatString:'foo'

o  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.

Usage example(s):

     'stx:libbasic' asPackageId

o  asPlainString
return myself as a plain string without any emphasis
Return myself - I am a string.
Subclasses which do no represent plain strings must redefine this method.

o  asScaledDecimal
read a fixedPoint number from the receiver.
Notice, that a ConversionError may be raised during the read,
so you better setup some signal handler when using this method.

Usage example(s):

     '0.123' asScaledDecimal
     '12345' asScaledDecimal
     '(1/5)' asScaledDecimal
     'foo' asScaledDecimal
     Object errorSignal 
        handle:[:ex | ex return:0] 
        do:['foo' asScaledDecimal]  

o  asScaledDecimal: scale
read a fixedPoint number with scale number of post-decimal digits
from the receiver. Scale controls the number of displayed digits,
not the number of actually valid digits.
Notice, that a ConversionError may be raised during the read,
so you better setup some signal handler when using this method.

Usage example(s):

     '0.123' asScaledDecimal:2
     '123456' asScaledDecimal:2
     ('3.14157' asScaledDecimal:1) asScaledDecimal:5
     '3.14157' asScaledDecimal:2
     'foo' asScaledDecimal:2

o  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.

Usage example(s):

     'hello' asSingleByteStringIfPossible
     'hello' asText asSingleByteStringIfPossible
     'hello' asUnicodeString asText asSingleByteStringIfPossible
     'hello' asUnicodeString asSingleByteStringIfPossible

o  asSingleByteStringReplaceInvalidWith: replacementCharacter
return the receiver converted to a 'normal' string,
with invalid characters replaced by replacementCharacter.
Can be used to convert from 16-bit strings to 8-bit strings
and replace characters above code-255 with some replacement.

o  asString
return myself - I am a string

o  asStringCollection
return a collection of lines from myself.

Usage example(s):

     'hello\world\1\2\3' withCRs asStringCollection first      => 'hello'
     c'hello\nworld\n1\n2\n3' asStringCollection first         => 'hello'
     c'hello\r\nworld\r\n1\r\n2\r\n3' asStringCollection first => c'hello\r' attenion: includes return charactern  
     'hello\' withCRs asStringCollection                       => StringCollection('hello')
     'hello' asStringCollection                                => StringCollection('hello')
     '' asStringCollection                                     => StringCollection()

o  asStringWithBitsPerCharacterAtLeast: numRequiredBitsPerCharacter
return the receiver in a representation which supports numRequiredBitsPerCharacter.
I.e. if required, convert to a Unicode16 or Unicode32 string

Usage example(s):

     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.

o  asSymbol
Return a unique symbol with the name taken from the receiver's characters.
The receiver should be a singleByte-String;
if not, an utf8 encoded version (with BOM) is returned as symbol.

Usage example(s):

     'abc' asSymbolIfInterned
     'abc' asSymbol

     Symbol allowWideSymbols:true.
     'ΔV' asSymbolIfInterned
     'ΔV' asSymbol
     'ϣ0' asSymbolIfInterned   
     'ϣ0' asSymbol   

o  asSymbolIfInterned
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]
but slightly faster, since the symbol lookup operation is only performed once.
The receiver should be a singleByte-String;
if not, an utf8 encoded version (with BOM) is tried as symbol.

Usage example(s):

     (Unicode16String with:(Character value:16rFFFF)) asSymbolIfInterned
     (Unicode16String with:(Character value:16rFFFF)) asSymbol

     'new' asUnicodeString asSymbolIfInterned
     'new' asText asSymbolIfInterned
     'new' asUnicodeString asText asSymbolIfInterned

o  asSymbolIfInternedOrSelf
If a symbol with the receiver's characters is already known, return it.
Otherwise, return self.
This can be used to query for an existing symbol and is the same as:
self knownAsSymbol ifTrue:[self asSymbol] ifFalse:[self]
but slightly faster, since the symbol lookup operation is only performed once.
The receiver must be a singleByte-String.
TwoByte- and FourByteSymbols are (currently ?) not allowed.

Usage example(s):

     (Unicode16String with:(Character value:16rFFFF)) asSymbolIfInternedOrSelf
     'new' asUnicodeString asSymbolIfInternedOrSelf
     'new' asText asSymbolIfInternedOrSelf
     'new' asUnicodeString asText asSymbolIfInternedOrSelf

o  asText
return a Text-object (string with emphasis) from myself.

o  asTimeDuration
return an TimeDuration object from the parsing the receiver string.
Notice, that a ConversionError may occur during the read,
so you better setup some exception handler when using this method.

Usage example(s):

     Time now asTimeDuration
     10 asTimeDuration
     10 seconds asTimeDuration
     '10m 20s' asTimeDuration
     'blabla' asTimeDuration

o  asTimestamp
convert the receiver into an Timestamp.
Notice, that a ConversionError may occur during the read,
so you better setup some exception handler when using this method.

Usage example(s):

     'blablavla' asTimestamp
     '2014-11-10 21:30:22.444' asTimestamp
     '2014-11-10 21:30:22.444Z' asTimestamp
     '2014-11-10 21:30:22.444+0200' asTimestamp

o  asTitlecase
return a version of the receiver, where the first character is converted to titlecase,
and everything else to lowercase.
See the comment in Character on what titlecase is.

Usage example(s):

     'helloWorld' asTitlecase
     'HelloWorld' allBold asTitlecase
     'HELLOWORLD' asTitlecase
     'helloworld' asTitlecase

o  asTitlecaseFirst
return a version of the receiver, where the first character is converted to titlecase.
Titlecase is much like uppercase for most characters, with the exception of some combined
(2-character glyphs), which consist of an upper- and lower-case characters.
If the first character is already titlecase, or there is no titlecasepercase for it, return the
receiver.

Usage example(s):

     'helloWorld' asTitlecaseFirst
     'helloWorld' allBold asTitlecaseFirst
     'HelloWorld' asTitlecaseFirst

o  asTwoByteString
return the receiver converted to a two-byte string.
Will be obsolete soon - use asUnicode16String.

o  asURI
return an URI with string taken from the receiver

o  asURL
( an extension from the stx:libhtml package )
return an URL-object from myself.

Usage example(s):

     'http://www.exept.de:80/index.html' asURL host
     '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

o  asUUID
return self as a UUID.
Notice, that a ConversionError may be raised during the read,
so you better setup some signal handler when using this method.

Usage example(s):

     UUID genUUID asString asUUID
     '{EAB22AC0-30C1-11CF-A7EB-0000C05BAE0B}' asUUID
     '{EAB22AC0-30C1-11CF-A7EB-0000C05BAE0B}' asUnicodeString asUUID
     'EAB22AC0-30C1-11CF-A7EB-0000C05BAE0B' asUUID
     'EAB22AC0-30C1-11CF-A7EB-0000C05BAE0B quatsch' asUUID
     'quark EAB22AC0-30C1-11CF-A7EB-0000C05BAE0B' asUUID

o  asUnicode16String
return the receiver in a two-byte per character representation.
Normally, the internal ST/X representation should be transparent and not
of the programmer's concern; except when strings are passed to the outside world,
such as wide-string ffi calls or file contents.
This will raise an error if any non-16bit character is encountered
Notice: surrogate pairs are explicitly NOT generated here, because the generated
unicode16String is usually generated to be passed to external programs or Windows-APIs
which do not care for/know about surrogate pairs.
See asUnicode16StringWithSurrogatePairs which does that for data exchange with partners
which do know about it

Usage example(s):

     'abc' asUnicode16String    
     ('abc',(Character value:0x10000)) asUnicode16String
     ('abc',(Character value:0x10000)) asUnicode16StringWithSurrogatePairs

o  asUnicode16StringReplaceInvalidWith: replacementCharacter
return the receiver converted to a 'normal' 16-bit string,
with invalid characters replaced by replacementCharacter.
Can be used to convert from 32-bit strings to 16-bit strings
and replace characters above code-0xFFFF with some replacement.

Usage example(s):

     ('abc',(Character value:0x10000)) asUnicode16StringReplaceInvalidWith:$*

o  asUnicode16StringWithSurrogatePairs
return the receiver in a two-byte per character representation.
Same as asUnicode16String, but will generate a surrogate pair,
if any non-16bit character is encountered.
Normally, the internal ST/X representation should be transparent and not
of the programmer's concern; except when strings are passed to the outside world,
such as wide-string ffi calls or file contents.

Usage example(s):

     'abc' asUnicode16String                               => 'abc'  (unicode16String instance)
     'abc' asUnicode16StringWithSurrogatePairs             => 'abc'  (unicode16String instance)
     ('abc',(Character value:0x10000)) asUnicode16String   => error
     ('abc',(Character value:0x10000)) asUnicode16StringWithSurrogatePairs => (unicode16String instance)

o  asUnicode16StringZ
return the receiver in a two-byte per character representation.
Make sure that is zero terminated (last char is 16r0000).
Normally, the internal ST/X representation should be transparent and not
of the programmer's concern; except when strings are passed to the outside world,
such as wide-string ffi calls or file contents.

Usage example(s):

        '' asUnicode16StringZ
        'abc' asUnicode16StringZ
        'abc' asUnicode16String asUnicode16StringZ

o  asUnicode32String
return the receiver in a four-byte per character representation.
Normally, the internal ST/X representation should be transparent and not
of the programmer's concern; except when strings are passed to the outside world,
such as wide-string ffi calls or file contents.

o  asUnicodeString
return the receiver in a two-byte per character representation.
Normally, the internal ST/X representation should be transparent and not
of the programmer's concern; except when strings are passed to the outside world,
such as wide-string ffi calls or file contents.

Usage example(s):

     'Hello World' asUnicodeString

o  asUnixFilename
return a UnixFilename with pathname taken from the receiver

o  asUppercase
return a copy of myself in uppercase letters

Usage example(s):

     'helloWorld' asUppercase
     'helloWorld' asUppercaseFirst
     (Character value:16rB5) asString asUppercase   -- needs 16 bits !
     (Character value:16rFF) asString asUppercase   -- needs 16 bits !
     'āăąćĉ' allBold asUppercase   -- needs 16 bits !

o  asUppercaseFirst
return a version of the receiver, where the first character is converted to uppercase.
If the first character is already uppercase, or there is no uppercase for it, return the
receiver.

Usage example(s):

     'helloWorld' asUppercase
     'helloWorld' allBold asUppercaseFirst
     'helloWorld' asUppercaseFirst
     'HelloWorld' asUppercaseFirst
      #asUppercaseFirst asUppercaseFirst
      #asUppercaseFirst allBold asUppercaseFirst

o  asUppercaseLast
return a copy of myself where the last character is
converted to uppercase.

Usage example(s):

     'HelloWorld' asUppercase
     '' asUppercaseLast           
     'HelloWorld' asUppercaseLast 
     'HelloWorld' allBold asUppercaseLast 

o  asUtcTimestamp
convert the receiver into an UtcTimestamp (Time is interpreted in the UTC timezone).
Notice, that a ConversionError may be raised during the read,
so you better setup some signal handler when using this method.

Usage example(s):

     '2014-11-10 21:30:22.444' asUtcTimestamp
     'foo' asUtcTimestamp

o  asValidIdentifier
convert a string to a valie Smalltalk/Javascript identifier.
Answer myself, if I do not contain invalid charcters.

Usage example(s):

     'hello world' asValidIdentifier
     'hello+world' asValidIdentifier
     '' asValidIdentifier
     '12abc' asValidIdentifier

o  asVersionNumberCollection
Convert a string like 1.2.3a to an Array of numbers (or string, if not a number).
Remove zeroes from the end.

Usage example(s):

     '1' asVersionNumberCollection.
     '1.1' asVersionNumberCollection.
     '1.1a' asVersionNumberCollection.
     '1.1.0' asVersionNumberCollection.
     '01.01.0' asVersionNumberCollection.
     'expecco_18_1_0' asVersionNumberCollection.

o  literalArrayEncoding
encode myself as an array literal, from which a copy of the receiver
can be reconstructed with #decodeAsLiteralArray.

o  scanf: dataStreamOrString
( an extension from the stx:libbasic2 package )
Return a Collection of objects found in the Character Stream
<dataStream> as interpreted according to the receiver.
The receiver is assumed to be a conversion control string as
specified in the Unix C-language manual page for scanf(3).
For copyright information, see goodies/String-printf_scanf.chg

Usage example(s):

     '%d %x' scanf:(ReadStream on:'1234 ff00')
     '%d %s' scanf:(ReadStream on:'1234 ff00')
     '%d %b' scanf:(ReadStream on:'1234 1111')
     '%d %f' scanf:(ReadStream on:'1234 1111')
     '%d %f' scanf:(ReadStream on:'1234 1111.2345')
     '%d %q' scanf:(ReadStream on:'1234 1111.2345')

o  sscanf: string
( an extension from the stx:libbasic2 package )
Return a Collection of objects found in <string> as
interpreted according to the receiver.
The receiver is assumed to be a conversion control string as
specified in the Unix C-language manual page for scanf(3).
For copyright information, see goodies/String-printf_scanf.chg

Usage example(s):

     '%d %x' sscanf:'1234 ff00'     
     '%d 0x%x' sscanf:'1234 0xff00'     
     '%d %x %b' sscanf:'1234 ff00 1001'

o  string
return the receiver without any emphasis information
i.e. the underlying string. Thats what I am.

copying
o  , aStringOrCharacterOrAnyOther
redefined to allow characters and mixed strings to be appended.
This is nonStandard, but convenient

Usage example(s):

     'hello' , $1
     'hello' , (Character codePoint:1046)
     'hello' , '1'
     'hello' , 4711
     'hello' , (' world' asText allBold)
     'hello' , (JISEncodedString fromString:' world')
     (JISEncodedString fromString:'hello') , ' world'

     Transcript showCR:
         (Text string:'hello' emphasis:#italic) , (Text string:' world' emphasis:#bold)

     'hello',123,'world'
     'hello' allBold,123,'world'
     'hello',123,'world' allBold

o  ,, aString
concatenate with a newLine in between

Usage example(s):

     'hello' ,, 'world'

o  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.
See also contractAtBeginningTo:, contractAtEndTo: and contractTo:.
This is similar to contractTo:, but removes the characters,
whereas contractTo: replaces them by '...'

Usage example(s):

     '12345678901234'   chopTo:15    
     '123456789012345'  chopTo:15    
     '1234567890123456' chopTo:15    
     'aShortString' chopTo:15
     'aVeryLongNameForAStringThatShouldBeShortened' chopTo:15   

o  contractAtBeginningTo: maxLen
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.
See also contractAtEndTo:, contractTo: and chopTo:

Usage example(s):

     '12345678901234' contractAtBeginningTo:15
     '123456789012345' contractAtBeginningTo:15
     '1234567890123456' contractAtBeginningTo:15
     'aShortString' contractAtBeginningTo:15
     'aVeryLongNameForAStringThatShouldBeShortened' contractAtBeginningTo:15

o  contractAtEndTo: maxLen
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.
See also contractAtBeginningTo:, contractTo: and chopTo:

Usage example(s):

     '12345678901234' contractAtEndTo:15
     '123456789012345' contractAtEndTo:15
     '1234567890123456' contractAtEndTo:15
     'aShortString' contractAtEndTo:15
     'aVeryLongNameForAStringThatShouldBeShortened' contractAtEndTo:15

o  contractLeftTo: maxLen
if the receiver's size is less or equal to maxLen, return it.
Otherwise, return a copy of the receiver, where some characters
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 interest than the left.
See also contractAtBeginningTo:, contractAtEndTo:, contractTo: and chopTo:

Usage example(s):

     '12345678901234' contractLeftTo:15
     '123456789012345' contractLeftTo:15
     '1234567890123456' contractLeftTo:15
     'aShortString' contractLeftTo:15
     'aVeryLongNameForAStringThatShouldBeShortened' contractLeftTo:15
     'C:\Dokumente und Einstellungen\cg\work\bosch\dapas\hw_schnittstellen\DAPAS__HpibDLL.st' contractLeftTo:40

o  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.
See also contractAtBeginningTo:, contractAtEndTo: and chopTo:.
(This is similar to chopTo:, but replaces by '...',
whereas chopTo: removes characters)

Usage example(s):

     '12345678901234' contractTo:15
     '123456789012345' contractTo:15
     '1234567890123456' contractTo:15
     '12345678901234567' contractTo:15
     '123456789012345678' contractTo:15
     'aShortString' contractTo:15
     'aVeryLongNameForAStringThatShouldBeShortened' contractTo:15
     'C:\Dokumente und Einstellungen\cg\work\bosch\dapas\hw_schnittstellen\DAPAS__HpibDLL.st' contractTo:40
     ('1234567890123456789012345678901234567' contractTo:30) size
     ('1234567890123456789012345678901234567' contractTo:29) size

o  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.

Usage example(s):

     '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 '

o  copyReplaceAll: oldElement with: newElement
return a copy of the receiver as a string, where all elements equal to oldElement
have been replaced by newElement.

o  copyReplaceString: subString withString: newString
return a copy of the receiver, with all sequences of subString replaced
by newString (i.e. slice in the newString in place of the oldString).

Usage example(s):

     '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
     'ĀĂĄĆĈ' allBold copyReplaceString:'ĆĈ' withString:'foo'

     ('a string with spaces' copyReplaceAll:$  withAll:' foo ')
        copyReplaceString:'foo' withString:'bar'

o  copyWith: aCharacter
return a new string containing the receiver's characters
and the single new character, aCharacter.
This is different from concatentation, which expects another string
as argument, but equivalent to copy-and-addLast.
The code below cares for different width characters
(i.e. when appending a 16bit char to an 8bit string)

Usage example(s):

        'Hello World ' copyWith:$Ĉ  
        'Hello World ' allBold copyWith:$Ĉ.

o  restAfter: keyword withoutSeparators: strip
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
begins with something.

You may wonder why such a specialized method exists here
- this is so common when processing mailboxes,
rcs files, nntp/pop3 responses, that is was considered worth
a special method here to avoid having the code below a hundred
times in variuos places.

Usage example(s):

     'foo: hello world' restAfter:'foo:' withoutSeparators:true
     'funny: something' restAfter:'foo:' withoutSeparators:true

     'foo:     hello world    ' restAfter:'foo:' withoutSeparators:true
     'foo:     hello world    ' restAfter:'foo:' withoutSeparators:false

o  splitAtString: subString withoutSeparators: stripBoolean
If the receiver is of the form:
<left><subString><right>
return a collection containing left and right only.
If strip is true, remove whiteSpace in the returned substrings.

Usage example(s):

     'hello -> world' splitAtString:'->' withoutSeparators:false
     'hello -> world' splitAtString:'->' withoutSeparators:true
     'hello -> ' splitAtString:'->' withoutSeparators:true
     'hello > error' splitAtString:'->' withoutSeparators:true

o  wrapForSize: maxLength
similar to splitForSize, but tries to keep words unsplitted.
Useful to wrap long lines eg. when presenting them in a warnbox.
Individual pieces may be smaller.
This is a somewhat q&d naive implementation, which may need more fine tuning

Usage example(s):

     'hello world123 this is a long line wrapped for size 10' wrapForSize:10 
     'hello world123 this is a long line wrapped for size 20' wrapForSize:20 
     'helloworld123 this is a long line wrapped for size 10' wrapForSize:10 
     'hello world123. This is a long line, wrapped for size 10' wrapForSize:10 
     'hello world123. This is a long line, wrapped for size 20' wrapForSize:20 

displaying
o  displayOn: aGC x: x y: y from: start to: stop
display the receiver on a GC

o  displayOn: aGC x: x y: y from: start to: stop opaque: opaque
display the receiver on a GC

o  displayOn: aGc x: x y: y opaque: opaque
display the receiver in a graphicsContext - this method allows
strings to be used like DisplayObjects.

o  displayOpaqueOn: aGC x: x y: y from: start to: stop
display the receiver on a GC

emphasis
o  actionForAll: aBlock
change the action block of all characters.
Some widgets use this like a href if clicked onto the text.

o  allBold
return a text object representing the receiver, but all boldified

Usage example(s):

     Transcript showCR:'hello' asText allBold
     Transcript showCR:'hello' allBold

o  allGray
return a text object representing the receiver, but in gray color.
This is used so often, that it's worth a utility here

Usage example(s):

     Transcript showCR:'hello' asText allBold allGray
     Transcript showCR:'hello' allBold allGray
     Transcript showCR:'hello' allGray

o  allItalic
return a text object representing the receiver, but all in italic

Usage example(s):

     Transcript showCR:'hello' asText allItalic
     Transcript showCR:'hello' allItalic

o  allNonBold
make all characters non-bold;
I already have no emphasis, so the receiver string is returned

o  allRed
return a text object representing the receiver, but in red color.
This is used so often, that it's worth a utility here

Usage example(s):

     Transcript showCR:'hello' asText allBold allRed
     Transcript showCR:'hello' allBold allRed
     Transcript showCR:'hello' allRed

o  allStrikedOut
return a text object representing the receiver, but all in strikeout

Usage example(s):

     Transcript showCR:'hello' asText allStrikedOut
     Transcript showCR:'hello' allStrikedOut

o  allUnderlined
return a text object representing the receiver, but all with underline

Usage example(s):

     Transcript showCR:'hello' asText allUnderlined
     Transcript showCR:'hello' allUnderlined

o  asActionLinkTo: aBlock
change the action block of all characters and colorize as a link.
Some widgets use this like a href if clicked onto the text
(for example, the system-browser's info at the bottom is such a widget).

Usage example(s):

     (Label new)
        label:('This is a link: ', ('browse' asActionLinkTo:[SystemBrowser default open]));
        width:300;
        open

o  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)

Usage example(s):

     (Label new)
        label:('This is a link: ', ('browse' asActionLinkTo:[SystemBrowser default open] info:'Open the browser'));
        width:300;
        open

o  asActionLinkToOpenWebBrowser
change the action block of all characters and colorize as a link,
to open a web page on the URL represented by the text

Usage example(s):

     (Label new)
        label:('This is a link: ', 'http://www.exept.de' asActionLinkToOpenWebBrowser);
        width:300;
        open

     (Label new)
        label:('click to open exept' asActionLinkToOpenWebBrowserOn:'http://www.exept.de');
        width:300;
        open

o  asActionLinkToOpenWebBrowserOn: aURL
change the action block of all characters and colorize as a link,
to open a web page on aURL

Usage example(s):

     (Label new)
        label:('This is a link: ', 'www.exept.de' asActionLinkToOpenWebBrowser);
        width:300;
        open

     (Label new)
        label:('click to open exept' asActionLinkToOpenWebBrowserOn:'www.exept.de');
        width:300;
        open

o  colorizeAllWith: aColor
return a text object representing the receiver, but all colorized

Usage example(s):

     Transcript showCR:('hello' colorizeAllWith:Color red)
     Transcript showCR:('world' colorizeAllWith:Color green darkened)

o  colorizeAllWith: fgColor on: bgColor
return a text object representing the receiver, but all colorized with
both fg and background color

Usage example(s):

     Transcript showCR:('hello' colorizeAllWith:Color red on:Color yellow)
     Transcript showCR:('world' colorizeAllWith:Color red)

o  emphasis
return the emphasis.
Since characterArrays do not hold any emphasis information,
nil (no emphasis) is returned here.

o  emphasis: emphasisCollection
Transcript showCR:('hello' emphasis:#(bold bold bold bold bold))

o  emphasisAt: characterIndex
return the emphasis at some index.
Since characterArrays do not hold any emphasis information,
nil (no emphasis) is returned here.

o  emphasisAtX: xOffset on: aGC
return the emphasis at a given x offset, or nil if there is none

o  emphasisCollection
return the emphasis.
Since characterArrays do not hold any emphasis information,
nil (no emphasis) is returned here.

o  emphasiseFrom: start to: stop with: newEmphasis
same as emphasizeFrom:to:with:

Usage example(s):

     'hello' emphasizeFrom:2 with:#italic

     Transcript showCR:('hello' emphasizeFrom:2 with:#italic)

     (Text string:'hello') allBold 
        emphasiseFrom:2 to:4 with:#italic

o  emphasizeAllWith: emphasis
return a text object representing the receiver,
but all emphasized with emphasis

Usage example(s):

     Transcript showCR:('hello' emphasizeAllWith:#bold)
     Transcript showCR:('hello' emphasizeAllWith:(#color -> Color red))
     Transcript showCR:('hello' emphasizeAllWith:(#color -> Color red))

o  emphasizeFrom: startIndex count: count with: emphasis
Return a text object with its emphasis
set in a range of characters, given startIndex and count.

Usage example(s):

     'hello world' 
        emphasizeFrom:1 count:5 with:#bold

     (Text string:'hello world') 
        emphasizeFrom:1 count:5 with:#bold;
        emphasizeFrom:7 count:5 with:#italic

o  emphasizeFrom: startIndex to: stopIndex with: newEmphasis
return a text object with its emphasis
set to newEmphasis within some range.

Usage example(s):

     'hello' emphasizeFrom:3 with:#bold

     Transcript showCR:('hello' emphasizeFrom:2 with:#italic)

o  emphasizeFrom: startIndex with: newEmphasis
return a text object with its emphasis
set to newEmphasis from startIndex to the end

Usage example(s):

     'hello' emphasizeFrom:2 with:#bold

     Transcript showCR:('hello' emphasizeFrom:2 with:#bold)

o  emphasizeTo: endIndex with: newEmphasis
return a text object with its emphasis
set to newEmphasis from the beginning to endIndex

Usage example(s):

     'hello' emphasizeTo:3 with:#bold

     Transcript showCR:('hello' emphasizeTo:3 with:#bold)

o  makeSelectorBoldIn: aClass
the receiver represents some source code for a method in aClass.
Change myself to boldify the selector.
Not yet implemented (could easily use the syntaxHighlighter for this ...).
For protocol compatibility with other smalltalks

o  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)

Usage example(s):

     Transcript showCR:('hello' withBackgroundColor:#red)
     Transcript showCR:('world' withColor:#red)
     Transcript showCR:('hello' withBackgroundColor:Color red)
     Transcript showCR:('world' withColor:Color green darkened)

o  withColor: aColorOrColorSymbol
return a text object representing the receiver, but all 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)

Usage example(s):

     Transcript showCR:('hello' withColor:#red)
     Transcript showCR:('world' withColor:#blue)
     Transcript showCR:('hello' withColor:Color red)
     Transcript showCR:('world' withColor:Color green darkened)
     ('world' withColor:Color green darkened) withColor:nil

o  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)

Usage example(s):

     Transcript showCR:('hello' withColor:#red on:#blue)
     Transcript showCR:('hello' withColor:Color red on:Color blue)

o  withoutAnyColorEmphasis
for protocol compatibility with Text

o  withoutBackgroundColorEmphasis
for protocol compatibility with Text

o  withoutEmphasis
for protocol compatibility with Text

o  withoutEmphasis: emphasisToRemove
for protocol compatibility with Text

o  withoutForegroundColorEmphasis
for protocol compatibility with Text

encoding & decoding
o  asDenormalizedUnicodeString
return a new string containing the same characters, as a denormalized Unicode string.
This replaces diacritical chars (umlauts, accented chars etc) by
a sequence with combination characters.
(i.e. a plain character followed by a combining diacritical in the 0x03xx range)

Usage example(s):

     'Ö' asDenormalizedUnicodeString 
     'aÖÄx' asDenormalizedUnicodeString 
     'abc' asDenormalizedUnicodeString 
     'ṩ' asDenormalizedUnicodeString 

o  asNormalizedUnicodeString
return a new string containing the same characters, as a normalized Unicode string.
This replaces combination characters by corresponding single characters.
(i.e. diaresis and other combining diacriticals in the 0x03xx range).
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...

Usage example(s):

     self unicodeNormalizationMap
     ('O' , (Character value:16r0308)) asNormalizedUnicodeString -> 'Ö'
     ('O' , (Character value:16r0308)) asText asNormalizedUnicodeString -> 'Ö'
     ('O' , (Character value:16r0308) ,
      'A' , (Character value:16r0308)) asNormalizedUnicodeString -> 'ÖÄ'
     ('s' , (Character value:16r0323) , (Character value:16r0307)) asNormalizedUnicodeString -> 'ṩ'
     ('s' , (Character value:16r0307) , (Character value:16r0323)) asNormalizedUnicodeString -> 'ṩ'
     ('s' , (Character value:16r0307) , (Character value:16r0323)) asText asNormalizedUnicodeString -> 'ṩ'

o  decodeAsLiteralArray
given a literalEncoding in the receiver,
create & return the corresponding object.
The inverse operation to #literalArrayEncoding.

o  rot13
Usenet: from `rotate alphabet 13 places']
The simple Caesar-cypher encryption that replaces each English
letter with the one 13 places forward or back along the alphabet,
so that 'The butler did it!' becomes 'Gur ohgyre qvq vg!'
Most Usenet news reading and posting programs include a rot13 feature.
It is used to enclose the text in a sealed wrapper that the reader must choose
to open -- e.g., for posting things that might offend some readers, or spoilers.
A major advantage of rot13 over rot(N) for other N is that it
is self-inverse, so the same code can be used for encoding and decoding.

Usage example(s):

     'hello world' rot13
     'hello world' rot13 rot13

o  rot: n
Usenet: from `rotate alphabet N places']
The simple Caesar-cypher encryption that replaces each English
letter with the one N places forward or back along the alphabet,
so that 'The butler did it!' becomes 'Gur ohgyre qvq vg!' by rot 13
Most Usenet news reading and posting programs include a rot13 feature.
It is used to enclose the text in a sealed wrapper that the reader must choose
to open -- e.g., for posting things that might offend some readers, or spoilers.
A major advantage of rot13 over rot(N) for other N is that it
is self-inverse, so the same code can be used for encoding and decoding.

Usage example(s):

     'hello world' rot:13
     'hello world' allBold rot:13
     ('hello world' rot:13) rot:13

o  utf16Encoded
answer a Unicode16String, where characters out of the UTF-16 range are encoded
as two 16-bit values.

Usage example(s):

     'abcde1234' utf16Encoded
     'abcdeäöüß' utf16Encoded
     'hello äöü' utf16Encoded asByteArray
     'hello äöü' utf16Encoded encodeInto:#utf16BE
     'hello äöü' utf16Encoded encodeInto:#utf16LE
     'abcdeäöüß' asUnicode16String utf16Encoded
     'abcdeäöüß' asUnicode32String utf16Encoded

o  utf8Encoded
return the UTF-8 representation of a Unicode string.
The resulting string is only useful to be stored on some external file,
or sent to a communaction channel.
Not for being used inside ST/X.

Usage example(s):

     'hello' utf8Encoded asByteArray                             #[104 101 108 108 111]
     (Character value:16r40) asString utf8Encoded asByteArray    #[64]
     (Character value:16r7F) asString utf8Encoded asByteArray    #[127]
     (Character value:16r80) asString utf8Encoded asByteArray    #[194 128]
     (Character value:16rFF) asString utf8Encoded asByteArray    #[195 191]
     (Character value:16r100) asString utf8Encoded asByteArray   #[196 128]
     (Character value:16r200) asString utf8Encoded asByteArray   #[200 128]
     (Character value:16r400) asString utf8Encoded asByteArray   #[208 128]
     (Character value:16r800) asString utf8Encoded asByteArray   #[224 160 128]
     (Character value:16r1000) asString utf8Encoded asByteArray  #[225 128 128]
     (Character value:16r2000) asString utf8Encoded asByteArray  #[226 128 128]
     (Character value:16r4000) asString utf8Encoded asByteArray  #[228 128 128]
     (Character value:16r8000) asString utf8Encoded asByteArray  #[232 128 128]
     (Character value:16rFFFF) asString utf8Encoded asByteArray  #[239 191 191]
     (Character value:16r1FFFF) asString utf8Encoded asByteArray #[240 159 191 191]
     (Character value:16r3FFFF) asString utf8Encoded asByteArray #[240 191 191 191]
     (Character value:16rFFFFF) asString utf8Encoded asByteArray #[243 191 191 191]
     (Character value:16r3FFFFF) asString utf8Encoded asByteArray #[248 143 191 191 191]

     'abcde1234' asUnicode32String utf8Encoded
     'abcdeäöüß' asUnicode32String utf8Encoded

o  utf8EncodedOn: aStream
write the UTF-8 representation of myself to aStream.

inspecting
o  inspector2TabBytes
( an extension from the stx:libtool package )
ouch - ever tried to inspect a 5Mb string?

o  inspector2TabDiff
( an extension from the stx:libtool package )

o  inspector2TabForHexDump
( an extension from the stx:libtool package )
a tab, showing a hex dump; defined here, so that both byteArrays and other bulk data
containers can define it in their inspector2Tabs methods.

o  inspector2TabHTML
( an extension from the stx:libtool package )
use Smalltalk >> at:, to prevent HTMLDocumentView becoming a prereq of libbasic

o  inspector2TabText
( an extension from the stx:libtool package )

o  inspector2TabXMLTree
( an extension from the stx:libtool package )
extra tab to be shown in an Inspector2.

o  inspectorExtraAttributes
( an extension from the stx:libtool package )
extra (pseudo instvar) entries to be shown in an inspector.

o  inspectorValueListIconFor: anInspector
( an extension from the stx:libtool package )
returns the icon to be shown alongside the value list of an inspector

o  inspectorValueStringInListFor: anInspector
( an extension from the stx:libtool package )
returns a string to be shown in the inspector's list

matching - glob expressions
o  compoundMatch: aString
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.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     'f*' match:'foo'
     'b*' match:'foo'
     'f*;b*' match:'foo'
     'f*;b*' match:'bar'
     'f*;b*' compoundMatch:'foo'
     'f*;b*' compoundMatch:'bar'
     '*.png;*.gif' compoundMatch:'bar.jpg'
     '*.png;*.gif' compoundMatch:'bar.gif'

o  compoundMatch: aString caseSensitive: caseSensitive
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.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     'f*' match:'foo'               => true
     'b*' match:'foo'               => false  
     'f*;b*' match:'foo'            => false
     'f*;b*' match:'bar'            => false
     'f*;b*' compoundMatch:'foo'    => true
     'f*;b*' compoundMatch:'bar'    => true
     'f*;b*' compoundMatch:'xxx'    => false
     'f*;b*' compoundMatch:'Foo' caseSensitive:false    => true
     'f*;b*' compoundMatch:'Bar' caseSensitive:false    => true
     'f*;b*' compoundMatch:'ccc' caseSensitive:false    => false

     '*.png;*.gif' compoundMatch:'bar.GIF'                      => false
     '*.png;*.gif' compoundMatch:'bar.GIF' caseSensitive:false  => true

     '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    

o  compoundMatch: aString caseSensitive: caseSensitive withoutSeparators: withoutSeparators
like match, but the receiver may be a compound match pattern,
consisting of multiple simple GLOB patterns, separated by semicolons.
If withoutSeparators is true, spaces around individual patterns are stripped off.
This is usable with fileName pattern fields.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     'f*' match:'foo'
     'b*' match:'foo'
     'f*;b*' match:'foo'
     'f*;b*' match:'bar'
     'f*;b*' compoundMatch:'foo'
     'f*;b*' compoundMatch:'bar'
     '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

o  compoundMatch: aString ignoreCase: ignoreCase
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.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  findMatchString: matchString
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

Usage example(s):

     '1234567890123' findMatchString:'0*'             => 10
     'hello world bla foo baz' findMatchString:'b* '  => 13
     'hello world' findMatchString: 'w*'              => 7
     'hello world' findMatchString: 'W*'              => 0

o  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

Usage example(s):

      1234567890123
     'hello world bla foo baz' findMatchString:'b* '

o  findMatchString: matchString startingAt: index
like findString, but allowing GLOB match patterns.
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.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the argument is the match pattern

o  findMatchString: matchString startingAt: index caseSensitive: caseSensitive ifAbsent: exceptionBlock
like findString, but allowing GLOB match patterns.
find matchstring, 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.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the argument is the match pattern

Usage example(s):

     'one two three four' findMatchString:'o[nu]'
     'one two three four' findMatchString:'o[nu]' startingAt:3
     'one two three four one' findMatchString:'ONE' startingAt:3 caseSensitive:false ifAbsent:0
     'one two three four one' findMatchString:'ONE' startingAt:3 caseSensitive:true ifAbsent:0
     'one two three four ONE' findMatchString:'O#E' startingAt:1 caseSensitive:false ifAbsent:0
     'one two three four ONE' findMatchString:'O#E' startingAt:1 caseSensitive:true ifAbsent:0
      12345678901234567890

o  findMatchString: matchString startingAt: index ignoreCase: ignoreCase ifAbsent: exceptionBlock
like findString, but allowing GLOB match patterns.
find matchstring, 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.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the argument is the match pattern

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  globPatternAsRegexPattern
taking the receiver as a GLOB pattern,
return a corresponding regex pattern.
As regex does provide information about the matching substring,
it may be useful to apply a regex after a GLOB match,
in order to highlight matching substrings (eg. in a CodeView after a search).
If it turns out to be better, we may convert all GLOB searches to regex and use it right away.
(currently, it is not sure, if GLOB is not better for most simple searches, as they are encountered in typical real life)

Usage example(s):

     'hello' globPatternAsRegexPattern    => 'hello'
     'hello' allBold globPatternAsRegexPattern    => 'hello'
     'hello*' globPatternAsRegexPattern   => 'hello.*'
     '*hello*' globPatternAsRegexPattern  => '.*hello.*'
     'h###' globPatternAsRegexPattern     => 'h...'
     'h[0-9]' globPatternAsRegexPattern   => 'h[0-9]'
     'h[0-9][0-9][0-9]' globPatternAsRegexPattern => 'h[0-9][0-9][0-9]'
     'h[0-9]*' globPatternAsRegexPattern          => 'h[0-9].*'
     'h[-+]*' globPatternAsRegexPattern           => 'h[\+\-].*'
     'h[abc]*' globPatternAsRegexPattern          => 'h[a-c].*'
     'h[0-9abc]*' globPatternAsRegexPattern
     
     'hello world' matches:'h*w'                                  => false
     'hello world' matchesRegex:('h*w' globPatternAsRegexPattern) => false
     'hello world' matches:'h*d'                                  => true
     'hello world' matchesRegex:('h*d' globPatternAsRegexPattern) => true

o  includesMatchString: matchString
like includesString, but allowing GLOB match patterns.
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.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the argument is the match pattern

Usage example(s):

     'hello world' includesMatchString:'h*'
     '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]'

o  includesMatchString: matchString caseSensitive: caseSensitive
like includesString, but allowing GLOB match patterns.
find matchstring; if found, return true, otherwise return false.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the argument is the match pattern

Usage example(s):

     'hello world' includesMatchString:'h*' caseSensitive:true
     'hello world' includesMatchString:'h*' caseSensitive:false
     'Hello world' includesMatchString:'h*' caseSensitive:true
     'Hello world' includesMatchString:'h*' caseSensitive:false

     'hello world' includesMatchString:'h[aeiou]llo' caseSensitive:true
     'hello world' includesMatchString:'h[aeiou]llo' caseSensitive:false

     'hello world' includesMatchString:'wor*' caseSensitive:true
     'hello world' includesMatchString:'wor*' caseSensitive:false

     '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

o  match: aString
return true if aString matches the receiver,
where the receiver may contain GLOB meta-match characters
$* (to match any string)
$# (to match any character).
[...] to match a set of characters.
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),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     '#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'
     '*f*' match:'*f'
     '*ute*' match:'computer'
     '*uter' match:'computer'
     'uter*' match:'computer'
     '*ute*' match:''
     '[abcd]*' match:'computer'
     '[abcd]*' match:'komputer'
     '*some*compl*ern*' match:'this is some more complicated pattern match'
     '*some*compl*ern*' match:'this is another complicated pattern match'
     '*-hh' match:'anton-h'

o  match: aString caseSensitive: caseSensitive
return true if aString matches the receiver,
where the receiver may contain GLOB meta-match characters
$* (to match any string)
$# (to match any character)
[...] to match a set of characters.
If caseSensitive is false, lower/uppercase are considered the same.
The escape character is the backQuote.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     '*ute*' match:'COMPUTER' caseSensitive:false
     '*uter' match:'COMPUTER' caseSensitive:true
     '[abcd]*' match:'computer' caseSensitive:true
     '[abcd]*' match:'Computer' caseSensitive:true
     '[a-k]*' match:'komputer' caseSensitive:true
     '[a-k]*' match:'zomputer' caseSensitive:true
     '[a-k]*' match:'Komputer' caseSensitive:true
     '[a-k]*' match:'Komputer' caseSensitive:false
     '*some*compl*ern*' match:'this is some more complicated pattern match' caseSensitive:false
     '*some*compl*ern*' match:'this is another complicated pattern match' caseSensitive:false

     Time millisecondsToRun:[
        Symbol allInstancesDo:[:sym |
            '[ab]*' match:sym caseSensitive:true
        ]
     ].
     Time millisecondsToRun:[
        Symbol allInstancesDo:[:sym |
            '*at:*' match:sym caseSensitive:true
        ]
     ].

o  match: aString caseSensitive: caseSensitive escapeCharacter: escape
return true if aString matches the receiver,
where the receiver may contain GLOB meta-match characters
$* (to match any string)
$# (to match any character)
[...] to match a set of characters.
If caseSensitive is false, lower/uppercase are considered the same.
The escape character to treat the above meta characters as non-meta is
customizable by the escapeCharacter argument.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     '*ute*' match:'COMPUTER' caseSensitive:false
     '*uter' match:'COMPUTER' caseSensitive:true
     '[abcd]*' match:'computer' caseSensitive:true
     '[abcd]*' match:'Computer' caseSensitive:true
     '[a-k]*' match:'komputer' caseSensitive:true
     '[a-k]*' match:'zomputer' caseSensitive:true
     '[a-k]*' match:'Komputer' caseSensitive:true
     '[a-k]*' match:'Komputer' caseSensitive:false
     '*some*compl*ern*' match:'this is some more complicated pattern match' caseSensitive:false
     '*some*compl*ern*' match:'this is another complicated pattern match' caseSensitive:false

     Time millisecondsToRun:[
        Symbol allInstancesDo:[:sym |
            '[ab]*' match:sym caseSensitive:true
        ]
     ].
     Time millisecondsToRun:[
        Symbol allInstancesDo:[:sym |
            '*at:*' match:sym caseSensitive:true
        ]
     ].

o  match: aString escapeCharacter: escape
return true if aString matches the receiver,
where the receiver may contain GLOB meta-match characters
$* (to match any string)
$# (to match any character)
[...] to match a set of characters.
Lower/uppercase are considered different.
The escape character to treat the above meta characters as non-meta is
customizable by the escapeCharacter argument.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     'a\b\c\*' match:'a\b\c\d'
     'a\b\c\*' match:'a\b\c\d' escapeCharacter:nil

o  match: aString from: start to: stop caseSensitive: caseSensitive
return true if part of aString matches the receiver,
where the receiver may contain GLOB meta-match $*, $# or [...].
If caseSensitive is false, lower/uppercase are considered the same.
The escape character is the backQuote.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     '*ute*' match:'12345COMPUTER' from:1 to:5 caseSensitive:false
     '*ute*' match:'12345COMPUTER' from:6 to:13 caseSensitive:false

o  match: aString from: start to: stop caseSensitive: caseSensitive escapeCharacter: escape
return true if part of aString matches myself,
where the receiver may contain GLOB meta-match $*, $# or [...].
If caseSensitive is false, lower/uppercase are considered the same.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

Usage example(s):

     '*ute*' match:'12345COMPUTER' from:1 to:5 caseSensitive:false
     '*ute*' match:'12345COMPUTER' from:6 to:13 caseSensitive:false
     
     '*[12' match:'12345COMPUTER' from:6 to:13 caseSensitive:false -- gives a warning

o  match: aString from: start to: stop ignoreCase: ignoreCase
return true if part of aString matches myself,
where self may contain GLOB meta-match
characters $* (to match any string) or $# (to match any character)
or [...] to match a set of characters.
If ignoreCase is true, lower/uppercase are considered the same.
The escape character is the backQuote.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  match: aString from: start to: stop ignoreCase: ignoreCase escapeCharacter: escape
return true if part of aString matches myself,
where self may contain GLOB meta-match
characters $* (to match any string) or $# (to match any character)
or [...] to match a set of characters.
If ignoreCase is true, lower/uppercase are considered the same.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  match: aString ignoreCase: ignoreCase
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.
If ignoreCase is true, lower/uppercase are considered the same.
The escape character is the backQuote.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  match: aString ignoreCase: ignoreCase escapeCharacter: escape
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.
If ignoreCase is true, lower/uppercase are considered the same.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  matches: aGlobPatternString
return true if the receiver matches aGlobPatternString,
which may contain GLOB meta-match characters
$* (to match any string)
$# (to match any character)
[...] to match a set of characters.
Lower/uppercase are considered different.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

o  matches: aPatternString caseSensitive: caseSensitive
return true if the receiver matches aString,
where aPatternString may contain GLOB meta-match characters
$* (to match any string)
$# (to match any character)
[...] to match a set of characters.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

o  matches: aPatternString ignoreCase: ignoreCase
return true if the receiver matches aString,
where aPatternString may contain GLOB meta-match characters
$* (to match any string)
$# (to match any character)
[...] to match a set of characters.
Lower/uppercase are considered different.

NOTICE: match-meta character interpretation is like in unix-matching (glob),
NOT the ST-80 meaning.
NOTICE: this is GLOB, which is different from regex matching (see matchesRegex:)
NOTICE: the receiver is the match pattern

** This is an obsolete interface - do not use it (it may vanish in future versions) **

matching - phonetic
o  asKoelnerPhoneticCode
( an extension from the stx:libbasic2 package )
return a koelner phonetic code.
The koelnerPhonetic code is for the german language what the soundex code is for english;
it returns simular strings for similar sounding words.
There are some differences to soundex, though:
its length is not limited to 4, but depends on the length of the original string;
it does not start with the first character of the input.

Caveat: this phonetic code is especially suited for german words.
Please have a look at the other phonetic comparison operators found
in PhoneticStringUtilities.

Usage example(s):

     'claus' asKoelnerPhoneticCode = 'clause' asKoelnerPhoneticCode  => true
     'claus' asKoelnerPhoneticCode = 'Klause' asKoelnerPhoneticCode  => true

     #(
        'Müller'
        'Miller'
        'Mueller'
        'Mühler'
        'Mühlherr'
        'Mülherr'
        'Myler'
        'Millar'
        'Myller'
        'Müllar'
        'Müler'
        'Muehler'
        'Mülller'
        'Müllerr'
        'Muehlherr'
        'Muellar'
        'Mueler'
        'Mülleer'
        'Mueller'
        'Nüller'
        'Nyller'
        'Niler'
        'Czerny'
        'Tscherny'
        'Czernie'
        'Tschernie'
        'Schernie'
        'Scherny'
        'Scherno'
        'Czerne'
        'Zerny'
        'Tzernie'
        'Breschnew'
     ) do:[:w |
         Transcript show:w; show:'->'; showCR:(w asKoelnerPhoneticCode)
     ].

Usage example(s):

     'Breschnew' asKoelnerPhoneticCode -> '17863'
     'Breschnew' asKoelnerPhoneticCode -> '17863'
     'Breschneff' asKoelnerPhoneticCode -> '17863'
     'Braeschneff' asKoelnerPhoneticCode -> '17863'
     'Braessneff' asKoelnerPhoneticCode -> '17863'
     'Pressneff' asKoelnerPhoneticCode -> '17863'
     'Presznäph' asKoelnerPhoneticCode -> '17863'

o  asSoundexCode
( an extension from the stx:libbasic2 package )
return a soundex phonetic code or nil.
Soundex returns similar codes for similar sounding words, making it a useful
tool when searching for words where the correct spelling is unknown.
(read Knuth or search the web if you don't know what a soundex code is).

Caveat: 'similar sounding words' means: 'similar sounding in ENGLISH'
Please have a look at the other phonetic comparison operators found
in PhoneticStringUtilities.

Usage example(s):

     'claus' asSoundexCode
     'clause' asSoundexCode
     'close' asSoundexCode
     'claus' = 'clause'                              => false
     'claus' asSoundexCode = 'clause' asSoundexCode  => true
     'claus' asSoundexCode = 'Klause' asSoundexCode  => false

     'smalltalk' asSoundexCode   
     'smaltalk' asSoundexCode    
     'smaltak' asSoundexCode     
     'smaltok' asSoundexCode     
     'smoltok' asSoundexCode
     'aa' asSoundexCode
     'by' asSoundexCode
     'bab' asSoundexCode
     'bob' asSoundexCode
     'bop' asSoundexCode

padded copying
o  centerPaddedTo: newSize
return a new string consisting of the receiver's characters,
plus spaces up to length and center the receiver's characters in
the resulting string.
If the receiver's size is equal or greater than the length argument,
the original receiver is returned unchanged.

Usage example(s):

     'foo' centerPaddedTo:10
     123 printString centerPaddedTo:10

o  centerPaddedTo: size with: padCharacter
return a new string of length size, which contains the receiver
centered (i.e. padded on both sides).
Characters are filled with padCharacter.
If the receiver's size is equal or greater than the length argument,
the original receiver is returned unchanged.

Usage example(s):

     'foo' centerPaddedTo:11 with:$.
     'fooBar' centerPaddedTo:5 with:$.
     123 printString centerPaddedTo:10 with:$.
     (' ' , 123 printString) centerPaddedTo:10 with:$.
     (Float pi printString) centerPaddedTo:15 with:(Character space)
     (Float pi printString) centerPaddedTo:15 with:$-
     (' ' , Float pi class name) centerPaddedTo:15 with:$.
     'ĀĂĄĆĈ' allBold centerPaddedTo:15 with:$.

o  decimalPaddedTo: size and: afterPeriod at: decimalCharacter
return a new string of overall length size, which contains the receiver
aligned at the decimal-period column and afterPeriod characters to the right
of the period. The periodCharacter is passed as arguments (allowing for US and European formats
to be padded).
If the receiver's size is equal or greater than the length argument,
the original receiver is returned unchanged.
(sounds complicated ? -> see examples below).

Usage example(s):

     '123' decimalPaddedTo:10 and:3 at:$.      -> '   123    '
     '123' decimalPaddedTo:10 and:3 at:$.      -> '   123.000'
     '123.' decimalPaddedTo:10 and:3 at:$.     -> '   123.000'
     '123.1' decimalPaddedTo:10 and:3 at:$.    -> '   123.100'
     '123.1' decimalPaddedTo:10 and:3 at:$.    -> '   123.1  '
     '123.123' decimalPaddedTo:10 and:3 at:$.  -> '   123.123'

o  decimalPaddedTo: size and: afterPeriod at: decimalCharacter withLeft: leftPadChar right: rightPadChar
return a new string of overall length size, which contains the receiver
aligned at the decimal-period column and afterPeriod characters to the right
of the period.
Characters on the left are filled with leftPadChar.
If rightPadChar is nil, characters on the right are filled with leftPadCharacter too;
otherwise, if missing, a decimal point is added and right characters filled with this.
If the receiver's size is equal or greater than the length argument,
the original receiver is returned unchanged.
(sounds complicated ? -> see examples below).

Usage example(s):

     '123' decimalPaddedTo:10 and:3 at:$. withLeft:(Character space) right:nil     -> '   123    '
     '123' decimalPaddedTo:10 and:3 at:$. withLeft:(Character space) right:$0      -> '   123.000'
     '123.' decimalPaddedTo:10 and:3 at:$. withLeft:(Character space) right:$0     -> '   123.000'
     '123.1' decimalPaddedTo:10 and:3 at:$. withLeft:(Character space) right:$0    -> '   123.100'
     '123.1' decimalPaddedTo:10 and:3 at:$. withLeft:(Character space) right:nil   -> '   123.1  '
     '123.123' decimalPaddedTo:10 and:3 at:$. withLeft:(Character space) right:$0  -> '   123.123'

o  leftPaddedTo: size
return a new string of length size, which contains the receiver
right-adjusted (i.e. padded on the left).
Characters on the left are filled with spaces.
If the receiver's size is equal or greater than the length argument,
the original receiver is returned unchanged.

Usage example(s):

     'foo' leftPaddedTo:10
     'fooBar' leftPaddedTo:5
     123 printString leftPaddedTo:10

o  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.

Usage example(s):

     'foo' paddedTo:10
     123 printString paddedTo:10
     '12345678901234' paddedTo:10

printing & storing
o  article
return an article string for the receiver.
The original code only looked at the first character being a vowel;
this has been enhanced by some heuristics - not perfect, still.

Usage example(s):

     'uboot' article.        => 'a'
     'xmas' article.         => 'an'
     'alarm' article.        => 'an'
     'baby' article.         => 'a'
     'sql' article.          => 'an'
     'scr' article.          => 'an'
     'screen' article.       => 'a'
     'scrollbar' article.    => 'a'
     'scrs' article.         => 'an'
     'cvs' article.          => 'a'
     'cvssource' article.    => 'a'
     'symbol' article.       => 'a'
     'string' article.       => 'a'
     'rbparser' article.     => 'an'
     'scheme' article.       => 'a'
     'string' article.       => 'a'
     'style' article.        => 'a'
     'array' article.        => 'an'
     'symbolornil' article.  => 'a'
     'human' article.        => 'a'
     'http' article.         => 'an'
     'utf' article.          => 'a'
     'ldap' article.         => 'an'
     'uncle' article.        => 'an'
     'unit' article.         => 'a'
     'unknown' article.      => 'an'
     'one' article           => 'a'
      Smalltalk allClasses collect:#nameWithArticle

o  basicStoreOn: aStream
put the storeString of myself onto a aStream

o  basicStoreString
return a String for storing myself

Usage example(s):

     '' basicStoreString
     '''immutable'' string' asImmutableString basicStoreString
     'immutable string' asImmutableString basicStoreString

o  displayOn: aGCOrStream
Compatibility
append a printed desription on some stream (Dolphin, Squeak)
OR:
display the receiver in a graphicsContext at 0@0 (ST80).
This method allows for any object to be displayed in some view
(although the fallBack is to display its printString ...)

o  htmlString
for compatibility with HTML-dom nodes.
Generates a possibly escaped string for HTML

Usage example(s):

     'foobaz' htmlString   
     ('foo<',(Character value:0x250),'>baz') htmlString
     'foo bar baz' htmlString
     ('foo ',(Character value:0x250),' baz') htmlString

o  printOn: aStream
print the receiver on aStream

o  printString
return a string for printing - that's myself

o  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

Usage example(s):

     '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

o  printWithQuotesDoubledOn: aStream
put the raw storeString of myself on aStream;
this means that quotes are doubled inside

o  printXmlQuotedOn: aStream
convert aString to a valid XML string in ISO8859 encoding
that can be used for XML attributes.
Here line formatting characters ARE escaped.
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 ...

o  printXmlTextQuotedOn: aStream
convert aString to a valid XML string
that can be used for XML text.
Here line formatting characters are NOT escaped.
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

Usage example(s):

     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]

o  printf: args
( an extension from the stx:libbasic2 package )
Format and print the receiver with <args> 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).
For smalltalk specific formats,
see documentation in PrintfScanf >> format_printf.
For copyright information, see goodies/String-printf_scanf.chg

Usage example(s):

     ('%05x %d %f %o' printf:{ 123. 234*5. 1.234. 8r377 } )    
     Transcript showCR:('%05x %d %f %o' printf:{ 123. 234*5. 1.234. 8r377 } )

Usage example(s):

     Transcript showCR: 'Some examples:'!

     Transcript show:'''%#x %#X %03o%*.*s'' printf: #(16rABCD 16rEF 5 9 5 ''ghijklmn'') = .'.
     Transcript show: ('%#x %#X %03o%*.*s' printf: #(16rABCD 16rEF 5 9 5 'ghijklmn')).
     Transcript showCR: '.'

     Transcript show: '''%- 10.4s%.2e'' printf: (Array with: ''abcdefghijkl'' with: Float pi) = .'.
     Transcript show: ('%- 10.4s%.2e' printf: (Array with: 'abcdefghijkl' with: Float pi)).
     Transcript showCR: '.'

     Transcript show: '''%8.3f'' printf: (Array with: 200 sqrt negated) = .'.
     Transcript show: ('%8.3f' printf: (Array with: 200 sqrt negated)).
     Transcript showCR: '.'

     Transcript show: '''%c'' printf: #(16r41) = .'.
     Transcript show: ('%c' printf: #(16r41)).
     Transcript showCR: '.'

     Transcript show: '''%f%2s%s%s%s'' sscanf: ''237.0 this is a test'' = '.
     Transcript showCR: ('%f%2s%s%s%s'  sscanf: '237.0 this is a test') printString.

     Transcript show: '''%d%f%s'' sscanf: ''25 54.32e-01 monday'' = '.
     Transcript showCR: ('%d%f%s' sscanf: '25 54.32e-01 monday') printString.

     Transcript show: '''%f%*f %8[A-F0-9]%c%d 0x%x%f'' sscanf: ''12.45 1048.73 AE40Z527 0x75BCD15 34'' = '.
     Transcript showCR: ('%f%*f %8[A-F0-9]%c%d 0x%x%f' sscanf: '12.45 1048.73 AE40Z527 0x75BCD15 34') printString.

o  printf: args on: outStream
( an extension from the stx:libbasic2 package )
Format and print the receiver on <outStream> with <args>
formatted in C style, as specified in the Unix C-language manual page for printf(3).
For smalltalk specific formats,
see documentation in PrintfScanf >> format_printf.
For copyright information, see goodies/String-printf_scanf.chg

o  printfWith: arg1
( an extension from the stx:libbasic2 package )
Format and print the receiver with <arg1> 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).
For smalltalk specific formats,
see documentation in PrintfScanf >> format_printf

Usage example(s):

     ('%05x' printfWith:123)
     Transcript showCR:('%05x' printfWith:123)

o  printfWith: arg1 with: arg2
( an extension from the stx:libbasic2 package )
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).
For smalltalk specific formats, see documentation in PrintfScanf >> format_printf.

Usage example(s):

     Transcript showCR:('%d %05x' printfWith:123 with:234)
     ('%d %05x' printfWith:123 with:234)
     ('%d%02d' printfWith:2004 with:9)  

o  printfWith: arg1 with: arg2 with: arg3
( an extension from the stx:libbasic2 package )
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).
For smalltalk specific formats, see documentation in PrintfScanf >> format_printf.

Usage example(s):

     Transcript showCR:('%d %05x %08o' printfWith:123 with:234 with:345)

o  printfWith: arg1 with: arg2 with: arg3 with: arg4
( an extension from the stx:libbasic2 package )
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).
For smalltalk specific formats, see documentation in PrintfScanf >> format_printf.

Usage example(s):

     Transcript showCR:('%d %05x %08o %b' printfWith:123 with:234 with:345 with:123)

o  printfWith: arg1 with: arg2 with: arg3 with: arg4 with: arg5
( an extension from the stx:libbasic2 package )
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).
For smalltalk specific formats, see documentation in PrintfScanf >> format_printf.

Usage example(s):

     Transcript showCR:('%d %05x %08o %b' printfWith:123 with:234 with:345 with:123)

o  printf_formatArgCount
( an extension from the stx:libbasic2 package )
Return the number of arguments required/produced if the receiver is interpreted
as a printf/scanf format control string.
For smalltalk specific formats, see documentation in PrintfScanf.
For copyright information, see goodies/String-printf_scanf.chg

o  printf_printOn: outStream withData: args
( an extension from the stx:libbasic2 package )
Format and print the receiver on <outStream> with <args>
formatted in C style, as specified in the Unix C-language manual page for printf(3).

For copyright information, see goodies/String-printf_scanf.chg

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  storeUtf8On: aStream
put the storeString of myself on aStream.
Convert it to something that can be written to a plain ASCII file.
Implemented here as common code for subclasses.

o  unicodeStoreOn: aStream
write a store representation of myself without translating unicode to UTF-8.
This method is a kind of kludge and required because Unicode*String stores an UTF-8 encoded string.
Use it when you want to write a storeString to an encoded Stream

o  unicodeStoreString
return a UnicodeString for storing myself.
This method is a kind of kludge.
Use it when you want to write a storeString to an encoded Stream

o  xmlQuotedPrintString
convert aString to a valid XML string
that can be used for attributes, text, comments and PIs.
Returns the receiver, if there is nothing to quote.

private
o  printf_printArgFrom: formatStream to: outStream withData: argStream
( an extension from the stx:libbasic2 package )
Interpret the required number of arguments from <argStream>
according to the formatting information in <formatStream>.
Place the interpretation on <outStream>.
The interpretation is C printf(3) style, as
specified in the Unix C-language manual page for printf(3).
<formatStream> is assumed to be positioned just past
$%, and a complete control string is assumed available.

Return when the conversion control string is consumed.
Leave <formatStream> pointing past the last character in the conversion control string.

This code assumes that <formatStream> is formatted according to
specification, and error checking is minimal. Unexpected
results will be obtained by illegal control strings, or when
argument types do not match conversion codes, but it probably
won't dump core, like C does in such cases!

For copyright information, see goodies/String-printf_scanf.chg

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  scanf_scanArgFrom: dataStream to: collection format: format
( an extension from the stx:libbasic2 package )
Add to <collection> an object who's representation is found
in <dataStream> interpreted according to the conversion
control string in the Stream <format>.
<format> is assumed to be positioned just past a $%, and a complete control
string is assumed available.

Return when the conversion control string is consumed. Leave
<format> pointing past the last character in the conversion
control string, leave <dataStream> pointing past any width
specified in <format>, or at the first character that doesn't
make sense for the <format>.

For copyright information, see goodies/String-printf_scanf.chg

** This is an obsolete interface - do not use it (it may vanish in future versions) **

queries
o  argumentCount
treating the receiver as a message selector, return how many arguments would it take (ANSI)

Usage example(s):

     'foo:bar:' argumentCount
     #foo:bar: argumentCount
     'hello' argumentCount
     '+' argumentCount
     '++' argumentCount
     '+++' argumentCount
     '|' argumentCount
     '?' argumentCount
     '_' argumentCount
     '_:' argumentCount
     '_:_:' argumentCount
     '<->' argumentCount
     '<' argumentCount
     #'<' argumentCount

o  asGetter
return a corresponding getter method's selector.
I.e. #foo: asGetterSelector returns #foo

Usage example(s):

     #foo asGetter       =>  #foo
     #foo: asGetter      =>  #foo

o  asMutator
return a corresponding setter method's selector.
I.e. #foo asMutator returns #foo:

Usage example(s):

     #foo asMutator       =>  #foo:
     #foo: asMutator      =>  #foo:

o  bitsPerCharacter
return the underlying string's bitsPerCharacter
(i.e. is it a regular String or a TwoByteString)

Usage example(s):

     'hello' bitsPerCharacter
     'hello' asText allBold bitsPerCharacter

o  bytesPerCharacter
return the underlying string's bytesPerCharacter
(i.e. is it a regular String or a TwoByteString)

Usage example(s):

     'hello' bytesPerCharacter
     'hello' asUnicode16String bytesPerCharacter
     'hello' asText allBold bytesPerCharacter

o  bytesPerCharacterNeeded
return the actual underlying string's required bytesPerCharacter
(i.e. checks if all characters really need that depth)

Usage example(s):

     'hello' bytesPerCharacter       -> 1
     'hello' bytesPerCharacterNeeded -> 1
     
     'hello' asUnicode16String bytesPerCharacter       -> 2
     'hello' asUnicode16String bytesPerCharacterNeeded -> 1

o  camelCaseSeparatedWords
Breaks apart words written in camel case.
This is slightly different from the squeak implementation in that it handles digits
as being part of (typically a suffix) of the previous word,
whereas piecesCutWhereCamelCase treats them as separate words.
Also the handling of spaces is different.
For compatibility, both are present.

Usage example(s):

     'HelloWorld' camelCaseSeparatedWords => OrderedCollection('Hello' 'World')
     'abcDef'     camelCaseSeparatedWords => OrderedCollection('abc' 'Def')
     'UTFEncoder' camelCaseSeparatedWords => OrderedCollection('UTF' 'Encoder')
     'JisEncoder' camelCaseSeparatedWords => OrderedCollection('Jis' 'Encoder')
     'JISEncode'  camelCaseSeparatedWords => OrderedCollection('JIS' 'Encode')
     'FOOBar'     camelCaseSeparatedWords => OrderedCollection('FOO' 'Bar')
     
     'FOOBar12' camelCaseSeparatedWords  => OrderedCollection('FOO' 'Bar12')      
     'FOOBar12' piecesCutWhereCamelCase  => OrderedCollection('FOO' 'Bar' '12') 
     'FOOBar12AndSomething' camelCaseSeparatedWords  => OrderedCollection('FOO' 'Bar12' 'And' 'Something')       
     'FOOBar12AndSomething' piecesCutWhereCamelCase  => OrderedCollection('FOO' 'Bar' '12' 'And' 'Something')       

o  camelCaseSeparatedWordsDo: aBlock
Breaks apart words written in camel case and enumerates them.
This is slightly different from the squeak implementation in that it handles digits
as being part of (typically a suffix) of the previous word,
whereas piecesCutWhereCamelCase treats them as separate words.
Also the handling of spaces is different.
For compatibility, both are present.

Usage example(s):

     '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]
     'FOOBar'     camelCaseSeparatedWordsDo:[:w | Transcript showCR:w]
     'FOOBar12AndSomething' camelCaseSeparatedWordsDo:[:w | Transcript showCR:w]       

o  characterSize
answer the size in bits of my largest character (actually only 7, 8, 16 or 32)
Q: worth a primitive?

Usage example(s):

     'hello' characterSize                     
     'hello' asUnicode32String characterSize   
     'helloü' asUnicode32String characterSize  
     ('helloü',(Character value:0x1000)) asUnicode32String characterSize   
     'hello' asText allBold characterSize      

o  contains8BitCharacters

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  containsNon7BitAscii
return true, if the underlying string contains 8BitCharacters (or widers)
(i.e. if it is non-ascii)

Usage example(s):

     'hello' asUnicode32String containsNon7BitAscii
     'hello üöä' asUnicode32String containsNon7BitAscii
     'hello' asUnicode32String asText allBold containsNon7BitAscii
     'hello üö' asUnicode32String allBold containsNon7BitAscii

o  containsNon8BitElements
return true, if the receiver contains elements larger than a single byte

o  continuesWith: aString startingAt: startIndex
return true, if the receiver beginning at startIndex
contains the characters in aString.
Returns false if the search reaches the end of the receiver
before all characters have been compared.

Usage example(s):

     'hello world' continuesWith:'world' startingAt:6
     'hello world' continuesWith:'world' startingAt:7
     'hello' continuesWith:'llo' startingAt:3
     'hello' continuesWith:'llow' startingAt:3

o  countWords
return the number of words, which are separated by separators

Usage example(s):

     'hello world isnt this nice' countWords'

o  defaultElement

o  encoding
return the strings encoding, as a symbol.
Here, by default, we assume unicode-encoding.
Notice, that ISO-8859-1 is a true subset of unicode,
and that singleByteStrings are therefore both unicode AND
8859-1 encoded.

o  hasChangeOfEmphasis
return true, if the receiver contains non-empty emphasis information
i.e. any non-normal (=emphasized) characters

o  hasIcon
for LabelAndIcon compatibility

o  hasImage
for LabelAndIcon compatibility

o  heightOn: aGC
return the size of the receiver in device units if displayed on aGC

Usage example(s):

     'hello world' heightOn:(View new)

o  isAlphaNumeric
return true, if the receiver is some alphanumeric word;
i.e. consists of a letter followed by letters or digits.

Usage example(s):

     'helloWorld' isAlphaNumeric
     'foo1234' isAlphaNumeric
     'f1234' isAlphaNumeric
     '1234' isAlphaNumeric
     '+' isAlphaNumeric

o  isBinarySelector
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

Usage example(s):

     'foo:bar:' isBinarySelector
     #foo:bar: isBinarySelector
     'hello' isBinarySelector
     '+' isBinarySelector
     '|' isBinarySelector
     '?' isBinarySelector
     ':' isBinarySelector
     'a:' isBinarySelector
     '->' isBinarySelector
     '<->' isBinarySelector
     '::' isBinarySelector

o  isBlank
return true, if the receiver contains spaces only or is empty.
(this tests for spaces only, in contrast to #isWhitespace)

Usage example(s):

     '' isBlank                            => true
     '' asUnicode16String isBlank          => true
     '   a    ' isBlank                    => false
     '        ' isBlank                    => true
     '        ' asUnicode16String isBlank  => true

o  isInfix
return true, if the receiver is a binary message selector

Usage example(s):

     #at:put: isInfix
     #at: isInfix
     #+ isInfix
     #size isInfix

o  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.

Usage example(s):

     #at:put: isKeyword
     #at: isKeyword
     #+ isKeyword
     #size isKeyword

o  isKeywordSelector
return true, iff there are only alphanumeric or underline characters separated by colons.
Must end with a colon.
You can use this to check an arbitrary string for being valid as a keyword.
If you have a valid selector at hand, and need to know if it is a keyword or not,
use #isKeyword, which is much faster.

Usage example(s):

     self assert:(':' isKeywordSelector not).
     self assert:(':a' isKeywordSelector not).
     self assert:('1:' isKeywordSelector not).
     self assert:('a:' isKeywordSelector).
     self assert:('_:' isKeywordSelector).
     self assert:('_a:' isKeywordSelector).
     self assert:('_1:' isKeywordSelector).
     self assert:('_1::' isKeywordSelector not).
     self assert:('_:_:' isKeywordSelector).
     self assert:('a:b:' isKeywordSelector).
     self assert:('aa:bb:' isKeywordSelector).
     self assert:('aa:bb:a' isKeywordSelector not).
     self assert:('1:2:' isKeywordSelector not).

o  isLowercaseFirst
return true, if the first character is a lowercase character.

Usage example(s):

     'helloWorld' isLowercaseFirst
     'HelloWorld' isLowercaseFirst

o  isNameSpaceSelector
Answer true if the receiver contains chars which form a nameSpace selector name.
These are of the form ':<ns>::<sel>', where ns is the NameSpace and sel is the regular selector.
For example, the #+ selector as seen by the Foo namespace would be actually #':Foo::+'.
This special format (a symbol starting with a colon) was chosen, because almost every other selector
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.

o  isNumeric
return true, if the receiver is some numeric word;
i.e. consists only of digits.

Usage example(s):

     'helloWorld' isNumeric    => false
     'foo1234' isNumeric       => false
     'f1234' isNumeric         => false
     '1234' isNumeric          => true
     '+' isNumeric             => false
     '-' isNumeric             => false
     '' isNumeric              => false
     '0' isNumeric             => true
     '0123a' isNumeric         => false

o  isUppercaseFirst
return true, if the first character is an uppercase character.

Usage example(s):

     'helloWorld' isUppercaseFirst
     'HelloWorld' isUppercaseFirst

o  isValidSmalltalkIdentifier
return true, if the receiver's characters make up a valid smalltalk identifier

Usage example(s):

     'foo' isValidSmalltalkIdentifier
     '1foo' isValidSmalltalkIdentifier
     '_foo' isValidSmalltalkIdentifier
     '_foo_bar_' isValidSmalltalkIdentifier
     'foo ' isValidSmalltalkIdentifier
     ' foo' isValidSmalltalkIdentifier

o  isWhitespace
return true, if the receiver is empty or contains only whitespace.
(this tests for spaces and returns and tabs, in contrast to #isBlank)

Usage example(s):

     '' isWhitespace                      => true
     '   ' isWhitespace                   => true
     '   \    \' withCRs isWhitespace     => true
     '   a\    \' withCRs isWhitespace    => false
     '   \    \a' withCRs isWhitespace    => false
     'a   \    \a' withCRs isWhitespace   => false

o  keywords
assuming the receiver is a keyword message selector,
return the individual keywords (i.e. break it up at colons)
and return these as a collection.
For binary and unary selectors, the result may be nonsense (an array containing the receiver).

Usage example(s):

     #at:put: keywords
     #at: keywords
     #+ keywords
     #size keywords

o  knownAsSymbol
for now, only single character strings are allowed as symbols.
This method is redefined in String.

o  leftIndent
if the receiver starts with whiteSpace, return the number of whiteSpace chars
at the left - otherwise, return 0.
If the receiver consists of whiteSpace only, return the receiver's size.

Usage example(s):

     '    hello' leftIndent
     'foo      ' leftIndent
     '         ' leftIndent
     ((Character tab),(Character tab),'foo') leftIndent

o  nameSpaceSelectorParts
Answer the namespace and baseSelector parts of a namespace selector.
Namespace selectors are those generated by sends from a method in a different
namespace; they are prefixed by ':'<ns>'::'.
You cannot easily change this algorithm here, as it is also known by the VM's lookup function.
Experimental

o  numArgs
treating the receiver as a message selector, return how many arguments would it take.
Please use argumentCount for ANSI compatibility.

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  numberOfLines
return the number of lines (separated by cr) of the receiver.
If the string ends with a cr, an empty line will be assumed at the end.
Thus, this returns the number of cr's PLUS 1.

Usage example(s):

     '1 one' numberOfLines             -> 1
     c'1 one\n' numberOfLines          -> 2
     c'1 one\n2 two' numberOfLines     -> 2
     '1 one\2 two\3 three\4 four\5 five' withCRs numberOfLines  -> 5
     '1 one\\\\2 two\3 three' withCRs numberOfLines             -> 6

o  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.

Usage example(s):

     'foo:' partsIfSelector
     'foo:bar:' partsIfSelector
     'foo::::' partsIfSelector
     #foo:bar: partsIfSelector
     'hello' partsIfSelector
     '+' partsIfSelector

o  speciesForSubcollection
answer the class, when splitting instances into subcollections

o  stringSpecies
return the underlying strings bitsPerCharacter
(i.e. is it a regular String or a TwoByteString)

Usage example(s):

     'hello' stringSpecies
     'hello' asText allBold stringSpecies

o  widthFrom: startIndex to: endIndex on: aGC
return ths size of part of the receiver in device units if displayed on aGC

Usage example(s):

     'hello world' widthFrom:1 to:5 on:(View new)
     'hello' widthOn:(View new)

o  widthOn: aGC
return ths size of the receiver in device units if displayed on aGC

Usage example(s):

     'hello world' widthOn:(View new)

special string converting
o  asUnixFilenameString
return a new string consisting of receiver's characters
with all \-characters replaced by /-characters.
If there are no backslashes, return the original

Usage example(s):

     'hello\world' asUnixFilenameString

o  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).

Usage example(s):

     'hello %1' expandNumericPlaceholdersWith:#('world')          
     'hello %(1)' expandNumericPlaceholdersWith:#('world')          
     'hello %(10)' expandNumericPlaceholdersWith:#('world')          
     'hello %1 %abc' expandNumericPlaceholdersWith:#('world')          
     'hello %1 %(abc)' expandNumericPlaceholdersWith:#('world')          

Usage example(s):

     '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')          

o  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.

Usage example(s):

     'hello a%b' expandPlaceholders

o  expandPlaceholders: escapeCharacter with: argArrayOrDictionary
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).

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'.
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)
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.

Usage example(s):

     '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)
     '%%(1)0 gives %(1)0' expandPlaceholdersWith:#(123)
     '%%10 gives %10' expandPlaceholdersWith:#(123)
     '%%(10) gives %(10)' expandPlaceholdersWith:#(123)
     '%test gives %1' expandPlaceholdersWith:#(123)
     'bla %1 bla' expandPlaceholdersWith:{ 'hello' allBold }
     'bla %1 bla' expandPlaceholdersWith:{ 'hello' }

Usage example(s):

     |dict|

     dict := Dictionary new.
     dict at:1 put:'one'.
     dict at:$a put:'AAAAA'.
     dict at:$b put:[ Time now ].
     dict at:'foo' put:[ Date today ].
     'hello $1 %a $b %(foo) $foo ' expandPlaceholders:$$ with:dict.
     'hello $1 %a $b %(foo) $foo ' expandPlaceholders:$% with:dict.

o  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.

Usage example(s):

     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
     'hello %1' allBold expandPlaceholders:$% with:#('world') on:Transcript.
     'hello %a%' expandPlaceholders:$% 
                    with:(Dictionary new at:'a' put:'world';yourself) 
                    on:Transcript.
     'hello %aa%' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
     'hello %(aa)%' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
     'hello %aa%' 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) %%next line' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '|%%|%%1|%%| gives |%|%1|%|' expandPlaceholders:$% with:#(foo) on:s.
     ]

Usage example(s):

     |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.
     ].

o  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.

Usage example(s):

     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
     'hello %1' allBold expandPlaceholders:$% with:#('world') on:Transcript.
     'hello %a%' expandPlaceholders:$% 
                    with:(Dictionary new at:'a' put:'world';yourself) 
                    on:Transcript.
     'hello %aa%' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
     'hello %(aa)%' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
     'hello %aa%' 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) %%next line' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '|%%|%%1|%%| gives |%|%1|%|' expandPlaceholders:$% with:#(foo) on:s.
     ]

Usage example(s):

     |dict|

     dict := Dictionary new.
     dict at:1 put:'one'.
     dict at:$a put:'AAAAA'.
     dict at:$b put:[ Time now ].
     dict at:'aKey' put:[ 4711 ].
     String streamContents:[:s|
         'hello $1 $a $b $(aKey) $(nonExistantKey)' expandPlaceholders:$$ with:dict on:s.
     ].

o  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.

Usage example(s):

     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
     'hello %a%' expandPlaceholders:$% 
                    with:(Dictionary new at:'a' put:'world';yourself) 
                    on:Transcript.
     'hello %aa%' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
     'hello %(aa)%' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
     'hello %aa%' 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) %%next line' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '|%%|%%1|%%| gives |%|%1|%|' expandPlaceholders:$% with:#(foo) on:s.
     ]

Usage example(s):

     |dict|

     dict := Dictionary new.
     dict at:1 put:'one'.
     dict at:$a put:'AAAAA'.
     dict at:$b put:[ Time now ].
     dict at:'aKey' put:[ 4711 ].
     String streamContents:[:s|
         'hello $1 $a $b $(aKey) $(nonExistantKey)' expandPlaceholders:$$ with:dict on:s.
     ].

o  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.

o  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.

Usage example(s):

     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) %%next line' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '|%%|%%1|%%| gives |%|%1|%|' expandPlaceholders:$% with:#(foo) on:s.
     ]

Usage example(s):

     |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.
     ].                                                    

o  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.

Usage example(s):

     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
     'hello %a%' expandPlaceholders:$% 
                    with:(Dictionary new at:'a' put:'world';yourself) 
                    on:Transcript.
     'hello %aa%' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
     'hello %(aa)%' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
     'hello %aa%' 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) %%next line' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '|%%|%%1|%%| gives |%|%1|%|' expandPlaceholders:$% with:#(foo) on:s.
     ]

Usage example(s):

     |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.
     ].

o  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.

Usage example(s):

     'hello %1' expandPlaceholders:$% with:#('world') on:Transcript.
     'hello %a%' expandPlaceholders:$% 
                    with:(Dictionary new at:'a' put:'world';yourself) 
                    on:Transcript.
     'hello %aa%' expandPlaceholders:$% with:(Dictionary new at:'a' put:'world';yourself) on:Transcript.
     'hello %(aa)%' expandPlaceholders:$% with:(Dictionary new at:'aa' put:'world';yourself) on:Transcript.
     'hello %aa%' 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) %%next line' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '|%%|%%1|%%| gives |%|%1|%|' expandPlaceholders:$% with:#(foo) on:s.
     ]

Usage example(s):

     |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.
     ].

o  expandPlaceholders: escapeCharacter with: argArrayOrDictionary 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 argArrayOrDictionary.
I.e. 'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this') results
in the new string 'hello world; how is this'.

As an extension, the argument may also be a dictionary, providing values for symbolic keys.
In this case, %a .. %z and %(...) are also allowed.
(%1..%9 require a numeric key in the dictionary, however)
Also, the values in argArrayOrDictionary may be blocks.

To get a '%' character, use a '%%'-escape.
To get an integer-indexed placeHolder followed by another digit, you must use %(digit).

See also bindWith:... for VisualAge compatibility.
Use %<cr> to insert a CR and %<tab> to insert a TAB.

Usage example(s):

     'hello %1' expandPlaceholders:$% with:#('world') 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) %%next line' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '%%test gives %test' expandPlaceholders:$% with:#(123) on:s.
        s cr.
        '|%%|%%1|%%| gives |%|%1|%|' expandPlaceholders:$% with:#(foo) on:s.
     ]

Usage example(s):

     |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.
     ].

o  expandPlaceholdersWith: argArrayOrDictionary
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'.

As an extension, the argument may also be a dictionary, providing
values for symbolic keys.
In this case, %a .. %z and %(...) are also allowed.
(%1..%9 require a numeric key in the dictionary, however)
Also, the values in argArrayOrDictionary may be blocks.

To get a '%' character, use a '%%'-escape.
To get an integer-indexed placeHolder followed by another digit, you must use %(digit).
See also bindWith:... for VisualAge compatibility.

Usage example(s):

self expandPlaceholdersWith:argArrayOrDictionary on:stream.

Usage example(s):

     'hello %1' expandPlaceholdersWith:#('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)
     '%%(1)0 gives %(1)0' expandPlaceholdersWith:#(123)
     '%%10 gives %10' expandPlaceholdersWith:#(123)
     '%%(10) gives %(10)' expandPlaceholdersWith:#(123)
     '%test gives %1' expandPlaceholdersWith:#(123)
     'bla %1 bla' expandPlaceholdersWith:{ 'hello' allBold }
     'bla %1 bla' expandPlaceholdersWith:{ 'hello' }
     ('bla %1 bla' withColor:Color red)
        expandPlaceholdersWith:{ 'hello' }
     ('bla %1 bla' withColor:Color red)
        expandPlaceholdersWith:{ 'hello' withColor:Color blue }

Usage example(s):

     |dict|

     dict := Dictionary new.
     dict at:1 put:'one'.
     dict at:$a put:'AAAAA'.
     dict at:$b put:[ Time now ].
     dict at:'foo' put:[ Date today ].
     'hello %1 %a %b %(foo)' expandPlaceholdersWith:dict

o  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.

Usage example(s):

     'hello %(abc) %1 %a %; %%' expandPlaceholdersWith:nil ifKeyAbsent:[:str :nm | str]
     'hello %(abc) %1 %a %; %%' allBold expandPlaceholdersWith:nil ifKeyAbsent:[:str :nm | str]

o  expandPlaceholdersWith: argArrayOrDictionary on: aStream
write the receiver to aStream, 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'.

As an extension, the argument may also be a dictionary, providing
values for symbolic keys.
In this case, %a .. %z and %(...) are also allowed.
(%1..%9 require a numeric key in the dictionary, however)
Also, the values in argArrayOrDictionary may be blocks.

To get a '%' character, use a '%%'-escape.
To get an integer-indexed placeHolder followed by another digit, you must use %(digit).

See also bindWith:... for VisualAge compatibility.
Use %<cr> to insert a CR and %<tab> to insert a TAB.

Usage example(s):

     String streamContents:[:s|
        'hello %1' expandPlaceholdersWith:#('world') on:s.
        s cr.
        'hello %1; how is %2' expandPlaceholdersWith:#('world' 'this') on:s.
        s cr.
        'hello %2; how is %1' expandPlaceholdersWith:#('world' 'this') on:s.
        s cr.
        '%1 plus %2 gives %3 ' expandPlaceholdersWith:#(4 5 9) on:s.
        s cr.
        '%%(1)0 gives %(1)0' expandPlaceholdersWith:#(123) on:s.
        s cr.
        '%%10 gives %10' expandPlaceholdersWith:#(123) on:s.
        s cr.
        '%%(10) gives %(10) %%next line' expandPlaceholdersWith:#(123) on:s.
        s cr.
        '%test gives %1' expandPlaceholdersWith:#(123) on:s.
     ]

Usage example(s):

     |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' expandPlaceholdersWith:dict on:s.
     ].

o  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.

Usage example(s):

     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

o  firstLine
return the first line of a multiline string

Usage example(s):

     'hello' firstLine          -> 'hello'
     '1\2\3' withCRs firstLine  -> '1'
     '\1\2\3' withCRs firstLine -> ''

o  tokensBasedOn: aCharacter
this is an ST-80 alias for the ST/X method
asCollectionOfSubstringsSeparatedBy:

Usage example(s):

     'hello:world:isnt:this nice' tokensBasedOn:$:
     'foo,bar,baz' tokensBasedOn:$,
     '/etc/passwd' asFilename readStream nextLine tokensBasedOn:$:

o  withCEscapes
return a new string consisting of 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
This is the opposite of withoutCEscapes.

Sigh: this is named completely wrong (opposite naming of withCRs/witoutCRs),
but it cannot be changed easily, as these methods are already used heavily

Usage example(s):

     '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

o  withCRs
return a new string consisting of the receiver's characters
with all \-characters replaced by cr-characters.
If there are no backslashes, return the original

Usage example(s):

     'hello\world' withCRs

o  withDoubleQuotes
wraps the receiver into double quotes.
This is the JavaScript standard quote function.

Usage example(s):

     'hello' withDoubleQuotes     

o  withEscapes
has been renamed; the name withEscapes is misleading

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  withMatchEscapes
return a copy of the receiver with all match characters escaped
by $\ characters (to be usable as a match string).
Return the receiver, if there are none.

Usage example(s):

     '*foo' withMatchEscapes
     '*ĀĂĄĆĈ' allBold withMatchEscapes
     '\*foo' withMatchEscapes
     '*foo' withMatchEscapes
     '\\*foo' withMatchEscapes
     'foo*' withMatchEscapes
     'foo\*' withMatchEscapes
     'foo\' withMatchEscapes
     'f*o*o' withMatchEscapes

o  withSeparatorsCompacted
return a new string with each sequence of whiteSpace replaced by a single space character.
Preserves a leading/trailing space.

Usage example(s):

     'hello wwww'         withSeparatorsCompacted
     'hello wwww' allBold withSeparatorsCompacted
     'hello    wwww'      withSeparatorsCompacted
     '  hello wwww'       withSeparatorsCompacted
     '  hello wwww   '    withSeparatorsCompacted
     '  hello    wwww   ' withSeparatorsCompacted
     'hel   lo www   w'   withSeparatorsCompacted

o  withSeparatorsReplacedBy: replacementCharacter
return a new string with each separator (whitespace) replaced by replacementCharacter.
Typically used with space as replacementCharacter

Usage example(s):

     'hello wwww' allBold withSeparatorsReplacedBy:$*
     'hello ww ww'        withSeparatorsReplacedBy:$*
     '  hello wwww'       withSeparatorsReplacedBy:$*
     'hel   lo www   w'   withSeparatorsReplacedBy:$*
     'hel
 lo www
w'   withSeparatorsReplacedBy:$*

o  withTabs
return a string consisting of the receiver's characters
where leading spaces are replaced by tabulator characters (assuming 8-col tabs).
Notice: if the receiver does not contain any tabs, it is returned unchanged;
otherwise a new string is returned.
Limitation: only the very first spaces are replaced
(i.e. if the receiver contains newLine characters,
no tabs are inserted after those lineBreaks)

Usage example(s):

     '12345678901234567890' withTabs
     '       8901234567890' withTabs
     '        901234567890' withTabs
     '               67890' withTabs
     '                7890' withTabs
     '                 890' withTabs
     '               ĀĂĄĆĈ' allBold withTabs

o  withTabsExpanded
return a string consisting of the receiver's characters,
where all tabulator characters are expanded into spaces (assuming 8-col tabs).
Notice: if the receiver does not contain any tabs, it is returned unchanged;
otherwise a new string is returned.
This does handle multiline strings.

Usage example(s):

     ('1' , Character tab asString , 'x') withTabsExpanded
     ('12345' , Character tab asString , 'x') withTabsExpanded
     ('123456' , Character tab asString , 'x') withTabsExpanded
     ('1234567' , Character tab asString , 'x') withTabsExpanded
     ('12345678' , Character tab asString , 'x') withTabsExpanded
     ('123456789' , Character tab asString , 'x') withTabsExpanded

     (String with:Character tab
             with:Character tab
             with:$1) withTabsExpanded

     (String with:Character tab
             with:$1
             with:Character tab
             with:$2) withTabsExpanded

     (String with:Character tab
             with:$1
             with:Character cr
             with:Character tab
             with:$2) withTabsExpanded

o  withTabsExpanded: numSpaces
return a string consisting of the receiver's characters,
where all tabulator characters are expanded into spaces (assuming numSpaces-col tabs).
Notice: if the receiver does not contain any tabs, it is returned unchanged;
otherwise a new string is returned.
This does handle multiline strings.

Usage example(s):

     ('1' , Character tab asString , 'x') withTabsExpanded
     ('1' , Character tab asString , 'x') withTabsExpanded:4
     ('12345' , Character tab asString , 'x') withTabsExpanded
     ('123456' , Character tab asString , 'x') withTabsExpanded
     ('1234567' , Character tab asString , 'x') withTabsExpanded
     ('12345678' , Character tab asString , 'x') withTabsExpanded
     ('123456789' , Character tab asString , 'x') withTabsExpanded

     (String with:Character tab
             with:Character tab
             with:$1) withTabsExpanded

     (String with:Character tab
             with:$1
             with:Character tab
             with:$2) withTabsExpanded

     (String with:Character tab
             with:$1
             with:Character cr
             with:Character tab
             with:$2) withTabsExpanded

     (Unicode16String with:Character tab
             with:$1
             with:Character cr
             with:Character tab
             with:$2) allBold withTabsExpanded

o  withoutAllSpaces
return a copy of the receiver with all whitespace removed

Usage example(s):

     'hello wwww'  withoutAllSpaces
     'hel   lo www   w'  withoutAllSpaces

o  withoutCEscapes
return a new string consisting of receiver's 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
\n newline character
\b backspace character
\f formfeed character
\t tab character
\e escape character
\\ the \ character itself
\nnn three digit octal number defining the characters ascii value
\xnn two digit hex number defining the characters ascii value
\unnnn four digit hex number defining the characters unicode value
\Unnnnnnnn eight digit hex number defining the characters unicode value
\other other

Notice, that \' is NOT a valid escape, since the general syntax of
string constants is not affected by this method.

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 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)

Starting with later stx versions, a new syntactic construct (cString) has been added;
written as c'...' the string characters are interpreted as in C.
I.e. 'a\nbc' withoutCEscapes is the same as c'a\nbc'.
However, the first is evaluated at execution time, whereas the second is evaluated at compilation time.

This is the opposite of withCEscapes.

Sigh: this is named completely wrong (opposite naming of withCRs/witoutCRs),
but it cannot be changed easily, as these methods are already used heavily

Usage example(s):

     'hello world' withoutCEscapes   => 'hello world'
     'hello\world' withoutCEscapes   => 'helloworld'
     'hello\world\' withoutCEscapes  => 'helloworld\'
     'hello world\' withoutCEscapes  => 'hello world\'
     'hello\tworld' withoutCEscapes  => 'hello  world'
     'hello\nworld\na\n\tnice\n\t\tstring' withoutCEscapes 
     'hello\tworld\n' withoutCEscapes 
     'hello\010world' withoutCEscapes
     'hello\r\nworld' withoutCEscapes
     'hello\r\n\x08world' withoutCEscapes
     '0\x0A1' withoutCEscapes
     '0\x081' 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
     c'-\X41-' => '-X41-'
     c'-\x41-' => '-A-'

o  withoutCRs
return a new collection consisting of receiver's elements
with all cr-characters replaced by \-characters.
This is the reverse operation of withCRs.

Usage example(s):

     'hello
world' withoutCRs

o  withoutLeadingSeparators
return a copy of myself without leading separators.
Notice: this does remove tabs, newline or any other whitespace.
Returns an empty string, if the receiver consist only of whitespace.

Usage example(s):

     '    foo    ' withoutLeadingSeparators
     'foo    '     withoutLeadingSeparators
     '    foo'     withoutLeadingSeparators
     '       '     withoutLeadingSeparators
     'foo'         withoutLeadingSeparators
     ('  ' , Character tab asString , ' foo   ') withoutLeadingSeparators inspect

o  withoutMatchEscapes
return a copy of the receiver with all $\ removed or
the receiver, if there are none.

Usage example(s):

     '*foo' withoutMatchEscapes
     '\*foo' withoutMatchEscapes
     '*foo' withoutMatchEscapes
     '\\*foo' withoutMatchEscapes
     'foo*' withoutMatchEscapes
     'foo\*' withoutMatchEscapes
     'foo\' withoutMatchEscapes
     'f\*o\*o' withoutMatchEscapes
     'ĀĂĄĆĈf\*o\*o' asText withoutMatchEscapes

o  withoutPrefix: aStringOrCharacter caseSensitive: caseSensitive
if the receiver startsWith aString, return a copy without it.
Otherwise return the receiver

Usage example(s):

     'Helloworld' withoutPrefix:'hello' caseSensitive:false
     'Helloworld' withoutPrefix:'foo' caseSensitive:false
     'Helloworld' withoutPrefix:$h caseSensitive:false
     'Helloworld' withoutPrefix:#( $h ) caseSensitive:false

o  withoutQuotes
remove quotes ($" and $') from the front and end of myself (if present and matching)"

o  withoutSeparators
return a copy of myself without leading and trailing whitespace.
(but whiteSpace in-between is preserved)
Whitespace is space, tab, newline, formfeed.
Use withoutSpaces, if you want to remove spaces only.

Usage example(s):

     '    foo    ' withoutSeparators
     '    foo' withoutSeparators
     'foo    ' withoutSeparators
     '       ' withoutSeparators
     ('  foo' , Character tab asString , '    ') withoutSeparators inspect
     '    foo    ' asUnicode16String withoutSeparators

o  withoutSpaces
return a copy of myself without leading and trailing spaces.
(but spaces in-between are preserved)
Notice: this does NOT remove tabs, newline or any other whitespace.
Use withoutSeparators for this.

Usage example(s):

     '    foo    ' withoutSpaces
     'foo    '     withoutSpaces
     '    foo'     withoutSpaces
     '       '     withoutSpaces
     'a     b'     withoutSpaces
     ('  foo' , Character tab asString , '    ') withoutSpaces inspect

o  withoutSuffix: aStringOrCharacter caseSensitive: caseSensitive
if the receiver endsWith aString, return a copy without it.
Otherwise return the receiver

Usage example(s):

     'helloworld' withoutSuffix:'world'
     'helloworld' withoutSuffix:'foo'

o  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.

Usage example(s):

     '    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

splitting & joining
o  splitWithoutSeparatorsBy: aCharacter
return a collection containing the subcollections (separated by aCharacter)
of the receiver. Whitespace is then removed around the extracted elements.
If aCharacter occurs multiple times in a row,
the result will contain empty collections.
If the receiver starts with aCharacter, an initial empty collection is added.
If the receiver ends with aCharacter, NO final empty collection is added.

Usage example(s):

     'a ; b  ; c;d' splitBy: $;.                  => StringCollection('a ' ' b  ' ' c' 'd')
     'a ; b  ; c;d' splitWithoutSeparatorsBy: $;. => StringCollection('a' 'b' 'c' 'd')

substring searching
o  findRangeOfString: subString
find a substring. if found, return the start- and endIndex;
if not found, return an empty interval.

Usage example(s):

     'hello world' findRangeOfString:'llo'
     'hello world' findRangeOfString:'ole'

o  findString: subString
find a substring. if found, return the index;
if not found, return 0.

Usage example(s):

     'hello world' findString:'llo'
     'hello world' findString:'ole'

o  findString: subString caseSensitive: caseSensitive
find a substring. if found, return the index;
if not found, return 0.

Usage example(s):

     'hello world' findString:'LLo' caseSensitive:true
     'hello world' findString:'LLo' caseSensitive:false

o  findString: subString ifAbsent: exceptionBlock
find a substring. If found, return the index;
if not found, return the result of evaluating exceptionBlock.

o  findString: subString ignoreCase: ignoreCase
find a substring. if found, return the index;
if not found, return 0.

** This is an obsolete interface - do not use it (it may vanish in future versions) **

o  findString: subString startingAt: index
find a substring, starting at index. if found, return the index;
if not found, return 0.

Usage example(s):

     'hello yello' findString:'llo' startingAt:1
     'hello yello' findString:'llo' startingAt:5
     'hello yello' findString:'llo' startingAt:15

o  findString: 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.

o  findString: subString startingAt: index ifAbsent: exceptionBlock caseSensitive: caseSensitive
find a substring, starting at index. if found, return the index;
if not found, return the result of evaluating exceptionBlock.

Usage example(s):

     'hello123foo' findString:'123' startingAt:1 ifAbsent:0 caseSensitive:false

o  includesString: aString
return true, if a substring is contained in the receiver

Usage example(s):

     'hello world' includesString:'hel'
     'hello world' includesString:'rld'
     'hello world' includesString:'llo'
     'hello world' includesString:'LLO'
     'hello world' includesString:''

o  includesString: aString caseSensitive: caseSensitive
return true, if a substring is contained in the receiver

Usage example(s):

     'hello world' includesString:'hel' caseSensitive:true
     'hello world' includesString:'HEL' caseSensitive:true
     'hello world' includesString:'HEL' caseSensitive:false

     'hello world' includesString:'wor' caseSensitive:true
     'hello world' includesString:'WOR' caseSensitive:true
     'hello world' includesString:'WOR' caseSensitive:false

o  includesStringOrMatches: aStringOrGLOBPattern caseSensitive: caseSensitive
if aString contains match characters,
a GLOB match is performed and I return true, if the receiver matches this pattern.
Otherwise return true, if I contain aStringOrGLOBPattern as substring.
This is such a common operation (with search fields in GUIs), that it is worth
a method.

Usage example(s):

     'hello world' includesStringOrMatches:'hel' caseSensitive:true
     'hello world' includesStringOrMatches:'*wo*d*' caseSensitive:true
     'hello world' includesStringOrMatches:'*wo*D*' caseSensitive:true
     'hello world' includesStringOrMatches:'*wo*D*' caseSensitive:false

o  indexOfString: aString
VSE and V'age compatibility.
find a substring (case sensitive).
If found, return the index; if not found, return 0.

Usage example(s):

     'hello world' indexOfString:'hello' -> 1
     'hello world' indexOfString:'world' -> 7
     'hello world' indexOfString:'World' -> 0
     'hello world' indexOfString:'World' caseSensitive:false -> 7

o  indexOfString: aString caseSensitive: caseSensitive
VSE and V'age compatibility

Usage example(s):

     'hello world' indexOfString:'hello' -> 1
     'hello world' indexOfString:'world' -> 7
     'hello world' indexOfString:'World' -> 0
     'hello world' indexOfString:'World' caseSensitive:false -> 7

o  indexOfString: aString caseSensitive: caseSensitive ifAbsent: exceptionValue
VSE and V'age compatibility

Usage example(s):

     '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

o  indexOfString: aString caseSensitive: caseSensitive startingAt: startIndex
VSE and V'age compatibility

o  indexOfString: aString caseSensitive: caseSensitive startingAt: startIndex ifAbsent: exceptionalValue
VSE and V'age compatibility

o  indexOfString: aString ifAbsent: exceptionValue
VSE and V'age compatibility

Usage example(s):

     '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

o  indexOfString: aString startingAt: startIndex
VSE and V'age compatibility

o  indexOfString: aString startingAt: startIndex ifAbsent: exceptionalValue
VSE and V'age compatibility

o  indexOfSubCollection: subString caseSensitive: caseSensitive
find a substring, starting at index. if found, return the index;
if not found, return the result of evaluating exceptionBlock.

o  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.

o  indexOfSubCollection: subString startingAt: index ifAbsent: exceptionBlock 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

Usage example(s):

     'Правда' indexOfSubCollection:'да' startingAt:1 ifAbsent:nil caseSensitive:true  
     'Правда' indexOfSubCollection:'ДА' startingAt:1 ifAbsent:nil caseSensitive:true   
     'Правда' indexOfSubCollection:'ДА' startingAt:1 ifAbsent:nil caseSensitive:false       
     'АБВГДЕЖ' asLowercase indexOfSubCollection:'ВГДЕ' startingAt:1 ifAbsent:nil caseSensitive:false.
     'АБВГДЕЖ' indexOfSubCollection:'ВГДЕ' startingAt:1 ifAbsent:nil caseSensitive:true.

o  indexOfSubCollection: subString startingAt: index ifAbsent: exceptionBlock caseSensitive: caseSensitive ignoreDiacritics: ignoreDiacritics
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
(see implementation in string, for a much faster algorithm)

Usage example(s):

     'bla depot bla dépots' indexOfSubCollection:'dep' startingAt:1 ifAbsent:0 caseSensitive:false ignoreDiacritics:true. 5
     'bla depot bla dépots' indexOfSubCollection:'dep' startingAt:6 ifAbsent:0 caseSensitive:false ignoreDiacritics:true. 0

     '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

o  lastIndexOfString: aString
VSE and V'age compatibility

Usage example(s):

123456789012
    'abcdefabcdef' lastIndexOfString:'abc'                => 7
    'abcdefabcdef' lastIndexOfString:'abc' startingAt:7   => 7
    'abcdefabcdef' lastIndexOfString:'abc' startingAt:6   => 1
    'abcdefabcdef' lastIndexOfString:'xxx' startingAt:6   => 0

o  lastIndexOfString: aString ifAbsent: exceptionValue
VSE and V'age compatibility

Usage example(s):

123456789012
    'abcdefabcdef' lastIndexOfString:'abc' ifAbsent:[999]    => 7
    'abcdefabcdef' lastIndexOfString:'xxx' ifAbsent:[999]    => 999

o  lastIndexOfString: aString startingAt: startIndex
VSE and V'age compatibility

Usage example(s):

123456789012
    'abcdefabcdef' lastIndexOfString:'abc'                 => 7 
    'abcdefabcdef' lastIndexOfString:'abc' startingAt:7    => 7
    'abcdefabcdef' lastIndexOfString:'abc' startingAt:6    => 1

o  lastIndexOfString: aString startingAt: startIndex ifAbsent: exceptionValue
VSE and V'age compatibility

Usage example(s):

123456789012
    'abcdefabcdef' lastIndexOfString:'abc'
    'abcdefabcdef' lastIndexOfString:'abc' startingAt:6
    'abcdefabcdef' lastIndexOfString:'xxx' startingAt:6 ifAbsent:999

o  occurrencesOfString: aSubString
count how often the argument aSubString is contained in the receiver

Usage example(s):

     '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'  

o  occurrencesOfString: aSubString caseSensitive: caseSensitive
count how often the argument aSubString is contained in the receiver

Usage example(s):

     '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  

o  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.

testing
o  isPlainString
return true, if the receiver is a plain string (without attributes);
true is returned here - redefinition of Object>>isPlainString.

o  isRegex

o  isString
return true, if the receiver is some kind of string;
true is returned here - redefinition of Object>>isString.

o  isUnary
Answer true if the receiver is a unary selector.
That is not a check for being a valid selector, but instead relies on
the selector being valid.

o  isUnarySelector
Answer true if the receiver contains only chars in an ANSI unary method selector, false otherwise.

Usage example(s):

     'foobar' isUnarySelector
     '_foobar' isUnarySelector
     '_' isUnarySelector
     'abc.def' isUnarySelector
     'abc123' isUnarySelector
     '123abc123' isUnarySelector
     '123abc' isUnarySelector
     '123' isUnarySelector

o  isUnicode16String

o  isUnicode32String
true if this is a 4-byte unicode string

o  isUnicodeString
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 use unicode encoding

o  isWideString
true if I require more than one byte per character

tracing
o  traceInto: aRequestor level: level from: referrer
double dispatch into tracer, passing my type implicitely in the selector

visiting
o  acceptVisitor: aVisitor with: aParameter
dispatch for visitor pattern; send #visitString:with: to aVisitor



ST/X 7.7.0.0; WebServer 1.702 at 20f6060372b9.unknown:8081; Sat, 27 Jul 2024 07:26:36 GMT