CharacterArray.st
changeset 10703 d1e981878c9c
parent 10698 08bfe7364c0f
child 10721 58e6950264cb
--- a/CharacterArray.st	Mon Sep 10 11:46:41 2007 +0200
+++ b/CharacterArray.st	Mon Sep 10 13:43:47 2007 +0200
@@ -195,25 +195,25 @@
     "skip whiteSpace"
     str skipSeparators.
     (str next == $') ifTrue:[
-        collected := WriteStream on:(self new).
-        [true] whileTrue:[
-            str atEnd ifTrue:[
-                "/ mhmh - reached the end without a closing quote
-                "/ looks like an error to me ...
-                ^ exceptionBlock value
-            ].
-            char := str next.
-            char == $' ifTrue:[
-                "/ look for another quote
-                str peekOrNil == $' ifFalse:[
-                    ^ collected contents
-                ].
-                str next.
-            ].
-            ((char ~~ Character return) or:[str peek ~~ Character lf]) ifTrue:[
-                collected nextPut:char.
-            ].
-        ]
+	collected := WriteStream on:(self new).
+	[true] whileTrue:[
+	    str atEnd ifTrue:[
+		"/ mhmh - reached the end without a closing quote
+		"/ looks like an error to me ...
+		^ exceptionBlock value
+	    ].
+	    char := str next.
+	    char == $' ifTrue:[
+		"/ look for another quote
+		str peekOrNil == $' ifFalse:[
+		    ^ collected contents
+		].
+		str next.
+	    ].
+	    ((char ~~ Character return) or:[str peek ~~ Character lf]) ifTrue:[
+		collected nextPut:char.
+	    ].
+	]
     ].
     ^ exceptionBlock value
 
@@ -237,7 +237,7 @@
 
     new := self new: anArray size.
     1 to: anArray size do:[:index |
-        new at: index put: (anArray at: index) asCharacter
+	new at: index put: (anArray at: index) asCharacter
     ].
     ^new
 
@@ -578,61 +578,61 @@
     coll := OrderedCollection new.
     idx := 1. end := aString size.
     [idx <= end] whileTrue:[
-        |char this|
-
-        char := aString at:idx.
-        char == $* ifTrue:[
-            previous ~~ #anyString ifTrue:[
-                this := #anyString
-            ]
-        ] ifFalse:[
-            char == $# ifTrue:[
-                previous ~~ #anyString ifTrue:[
-                    this := #any
-                ]
-            ] ifFalse:[
-                char == $[ ifTrue:[
-                    matchSet := IdentitySet new.
-                    idx := idx + 1.
-                    idx > end ifTrue:[^ nil].
-                    char := aString at:idx.
-                    c1 := nil.
-                    [char ~~ $]] whileTrue:[
-                        ((char == $-) and:[c1 notNil]) ifTrue:[
-                            idx := idx + 1.
-                            idx > end ifTrue:[^ nil].
-                            c2 := aString at:idx.
-                            c1 to:c2 do:[:c | matchSet add:c].
-                            c1 := nil.
-                            idx := idx + 1.
-                        ] ifFalse:[
-                            (char ~~ $]) ifTrue:[
-                                matchSet add:char.
-                                c1 := char.
-                                idx := idx + 1
-                            ]
-                        ].
-                        idx > end ifTrue:[^ nil].
-                        char := aString at:idx
-                    ].
-                    this := matchSet asString
-                ] ifFalse:[
-                    char == escape ifTrue:[
-                        idx := idx + 1.
-                        idx > end ifTrue:[
-                            "/ mhmh - what should we do here ?
-                            this := char
-                        ] ifFalse:[
-                            this := aString at:idx.
-                        ]
-                    ] ifFalse:[
-                        this := char
-                    ]
-                ]
-            ]
-        ].
-        this notNil ifTrue:[coll add:this. previous := this].
-        idx := idx + 1
+	|char this|
+
+	char := aString at:idx.
+	char == $* ifTrue:[
+	    previous ~~ #anyString ifTrue:[
+		this := #anyString
+	    ]
+	] ifFalse:[
+	    char == $# ifTrue:[
+		previous ~~ #anyString ifTrue:[
+		    this := #any
+		]
+	    ] ifFalse:[
+		char == $[ ifTrue:[
+		    matchSet := IdentitySet new.
+		    idx := idx + 1.
+		    idx > end ifTrue:[^ nil].
+		    char := aString at:idx.
+		    c1 := nil.
+		    [char ~~ $]] whileTrue:[
+			((char == $-) and:[c1 notNil]) ifTrue:[
+			    idx := idx + 1.
+			    idx > end ifTrue:[^ nil].
+			    c2 := aString at:idx.
+			    c1 to:c2 do:[:c | matchSet add:c].
+			    c1 := nil.
+			    idx := idx + 1.
+			] ifFalse:[
+			    (char ~~ $]) ifTrue:[
+				matchSet add:char.
+				c1 := char.
+				idx := idx + 1
+			    ]
+			].
+			idx > end ifTrue:[^ nil].
+			char := aString at:idx
+		    ].
+		    this := matchSet asString
+		] ifFalse:[
+		    char == escape ifTrue:[
+			idx := idx + 1.
+			idx > end ifTrue:[
+			    "/ mhmh - what should we do here ?
+			    this := char
+			] ifFalse:[
+			    this := aString at:idx.
+			]
+		    ] ifFalse:[
+			this := char
+		    ]
+		]
+	    ]
+	].
+	this notNil ifTrue:[coll add:this. previous := this].
+	idx := idx + 1
     ].
 
     ^ coll asArray
@@ -862,7 +862,7 @@
     ^ self size > 0 and: [self last isDigit]
 !
 
-findDelimiters:delimiters startingAt:start 
+findDelimiters:delimiters startingAt:start
     "Answer the index of the character within the receiver, starting at start, that matches one of the delimiters. If the receiver does not contain any of the delimiters, answer size + 1."
 
     |idx|
@@ -1262,94 +1262,94 @@
     out := WriteStream on:(self species uninitializedNew:self size).
 
     [in atEnd] whileFalse:[
-        c := in next.
-        c == $% ifTrue:[
-            c := in next.
-            out nextPut:c
-        ] ifFalse:[c ~~ $< ifTrue:[
-            out nextPut:c.
-        ] ifFalse:[
-            peekc := in peek.
-            [peekc == $<] whileTrue:[
-                out nextPut:$<.
-                peekc := in nextPeek.
-            ].
-            peekc == $n ifTrue:[
-                peekc := in nextPeek.
-                peekc == $> ifTrue:[
-                    in next.
-                    out cr.
-                ] ifFalse:[
-                    out nextPutAll:'<n'.
-                ]
-            ] ifFalse:[peekc == $t ifTrue:[
-                peekc := in nextPeek.
-                peekc == $> ifTrue:[
-                    in next.
-                    out tab.
-                ] ifFalse:[
-                    out nextPutAll:'<t'.
-                ]
-            ] ifFalse:[
-                peekc isDigit ifTrue:[
-                    "start an argument expansion ..."
-                    nr := Integer readFrom:in onError:nil.
-                    nr isNil ifTrue:[
-                        "this cannot happen (there is at least one digit)"
-                        self error:'invalid format' mayProceed:true.
-                        ^ self
-                    ].
-                    fmt := in next.
-                    (fmt ~~ $? and:[in peek ~~ $>]) ifTrue:[
-                        out nextPut:$<.
-                        nr printOn:out.
-                        out nextPut:fmt.
-                    ] ifFalse:[
-                        (nr between:1 and:argArray size) ifTrue:[
-                            arg := argArray at:nr.
-                        ] ifFalse:[
-                            arg := ''
-                        ].
-
-                        fmt == $p ifTrue:[
-                            "expand with args printString"
-                            arg printOn:out.
-                        ] ifFalse:[fmt == $s ifTrue:[
-                            "expand with arg itself"
-                            arg isText ifTrue:[
-                                out contentsSpecies isText ifFalse:[
-                                    out := (WriteStream on:Text new) nextPutAll:out contents; yourself.
-                                ].
-                                out nextPutAll:arg.
-                            ] ifFalse:[
-                                out nextPutAll:arg asString string.
-                            ]
-                        ] ifFalse:[fmt == $? ifTrue:[
-                            s1 := in upTo:$:.
-                            s2 := in nextUpTo:$>.
-                            arg == true ifTrue:[
-                                out nextPutAll:s1
-                            ] ifFalse:[
-                                out nextPutAll:s2
-                            ].
-                        ] ifFalse:[
-                            "what does VW do here ?"
-                            self error:'invalid format' mayProceed:true.
-                            ^ self
-                        ]]].
-                        c := in next.
-                        c ~~ $> ifTrue:[
-                            "what does VW do here ?"
-                            self error:'invalid format' mayProceed:true.
-                            ^ self
-                        ]
-
-                    ].
-                ] ifFalse:[
-                    out nextPut:$<.
-                ].
-            ]].
-        ]].
+	c := in next.
+	c == $% ifTrue:[
+	    c := in next.
+	    out nextPut:c
+	] ifFalse:[c ~~ $< ifTrue:[
+	    out nextPut:c.
+	] ifFalse:[
+	    peekc := in peek.
+	    [peekc == $<] whileTrue:[
+		out nextPut:$<.
+		peekc := in nextPeek.
+	    ].
+	    peekc == $n ifTrue:[
+		peekc := in nextPeek.
+		peekc == $> ifTrue:[
+		    in next.
+		    out cr.
+		] ifFalse:[
+		    out nextPutAll:'<n'.
+		]
+	    ] ifFalse:[peekc == $t ifTrue:[
+		peekc := in nextPeek.
+		peekc == $> ifTrue:[
+		    in next.
+		    out tab.
+		] ifFalse:[
+		    out nextPutAll:'<t'.
+		]
+	    ] ifFalse:[
+		peekc isDigit ifTrue:[
+		    "start an argument expansion ..."
+		    nr := Integer readFrom:in onError:nil.
+		    nr isNil ifTrue:[
+			"this cannot happen (there is at least one digit)"
+			self error:'invalid format' mayProceed:true.
+			^ self
+		    ].
+		    fmt := in next.
+		    (fmt ~~ $? and:[in peek ~~ $>]) ifTrue:[
+			out nextPut:$<.
+			nr printOn:out.
+			out nextPut:fmt.
+		    ] ifFalse:[
+			(nr between:1 and:argArray size) ifTrue:[
+			    arg := argArray at:nr.
+			] ifFalse:[
+			    arg := ''
+			].
+
+			fmt == $p ifTrue:[
+			    "expand with args printString"
+			    arg printOn:out.
+			] ifFalse:[fmt == $s ifTrue:[
+			    "expand with arg itself"
+			    arg isText ifTrue:[
+				out contentsSpecies isText ifFalse:[
+				    out := (WriteStream on:Text new) nextPutAll:out contents; yourself.
+				].
+				out nextPutAll:arg.
+			    ] ifFalse:[
+				out nextPutAll:arg asString string.
+			    ]
+			] ifFalse:[fmt == $? ifTrue:[
+			    s1 := in upTo:$:.
+			    s2 := in nextUpTo:$>.
+			    arg == true ifTrue:[
+				out nextPutAll:s1
+			    ] ifFalse:[
+				out nextPutAll:s2
+			    ].
+			] ifFalse:[
+			    "what does VW do here ?"
+			    self error:'invalid format' mayProceed:true.
+			    ^ self
+			]]].
+			c := in next.
+			c ~~ $> ifTrue:[
+			    "what does VW do here ?"
+			    self error:'invalid format' mayProceed:true.
+			    ^ self
+			]
+
+		    ].
+		] ifFalse:[
+		    out nextPut:$<.
+		].
+	    ]].
+	]].
     ].
     ^ out contents
 
@@ -1745,13 +1745,16 @@
     "/
     h := 0.
     self reverseDo:[:char |
-        h := (h bitShift:4) + char asciiValue.
-        h := h bitAnd:16rFFFFFFFF.
-        g := (h bitAnd: 16rF0000000).
-        g ~~ 0 ifTrue:[
-            h := h bitXor:(g bitShift:-24).
-            h := h bitXor:g.
-        ]
+"/ Sorry, stc cannot compile this (as of 10.9.2007)
+"/        h := (h bitShift:4) + char asciiValue.
+	h := (h bitShift:4).
+	h:= h + char asciiValue.
+	h := h bitAnd:16rFFFFFFFF.
+	g := (h bitAnd: 16rF0000000).
+	g ~~ 0 ifTrue:[
+	    h := h bitXor:(g bitShift:-24).
+	    h := h bitXor:g.
+	].
     ].
     "/
     "/ multiply by large prime to spread values
@@ -1762,14 +1765,14 @@
     ^ h
 
     "
-     'a' hash                   
-     'a' asUnicode16String hash 
-     'aa' hash                                      
-     'aa' asUnicode16String hash  
-     'ab' hash                                      
-     'ab' asUnicode16String hash   
-     'ab' hash                                      
-     'ab' asArray hash 
+     'a' hash
+     'a' asUnicode16String hash
+     'aa' hash
+     'aa' asUnicode16String hash
+     'ab' hash
+     'ab' asUnicode16String hash
+     'ab' hash
+     'ab' asArray hash
     "
 !
 
@@ -2001,8 +2004,8 @@
      'hello' asCollectionOfWords
      '' asCollectionOfWords
      '      ' asCollectionOfWords
-     ' foo bar__baz__bla__ bar ' asCollectionOfWords     
-     ' foo __bar__baz__bla__ bar ' asCollectionOfWords     
+     ' foo bar__baz__bla__ bar ' asCollectionOfWords
+     ' foo __bar__baz__bla__ bar ' asCollectionOfWords
     "
 !
 
@@ -2120,7 +2123,7 @@
      Notice, that errors may occur 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. 
+     in other smalltalks.
      For less strict integer reading, use Integer readFrom:aString"
 
     ^ Integer readFromString:self
@@ -2130,12 +2133,12 @@
      '-1234' asInteger
 
      The following raises an error:
-         '0.123' asInteger              <- reader finds more after reading 0
+	 '0.123' asInteger              <- reader finds more after reading 0
 
      whereas the less strict readFrom does not:
-         Integer readFrom:'0.123'       <- reader stops at ., returning 0
-
-     '0.123' asInteger   
+	 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]
 
@@ -2154,11 +2157,11 @@
     bitsPerCharacter := newStr bitsPerCharacter.
 
     1 to:mySize do:[:i |
-        c := (self at:i) asLowercase.
-        c bitsPerCharacter > bitsPerCharacter ifTrue:[
-            newStr := c stringSpecies fromString:newStr.
-        ].
-        newStr at:i put:c
+	c := (self at:i) asLowercase.
+	c bitsPerCharacter > bitsPerCharacter ifTrue:[
+	    newStr := c stringSpecies fromString:newStr.
+	].
+	newStr at:i put:c
     ].
     ^ newStr
 
@@ -2390,9 +2393,9 @@
 !
 
 asSymbolIfInterned
-    "If a symbol with the receivers characters is already known, return it. Otherwise, return nil. 
+    "If a symbol with the receivers characters is already known, return it. Otherwise, return nil.
      This can be used to query for an existing symbol and is the same as:
-        self knownAsSymbol ifTrue:[self asSymbol] ifFalse:[nil]
+	self knownAsSymbol ifTrue:[self asSymbol] ifFalse:[nil]
      but slightly faster, since the symbol lookup operation is only performed once.
      The receiver must be a singleByte-String.
      TwoByte- and FourByteSymbols are (currently ?) not allowed."
@@ -2548,11 +2551,11 @@
     bitsPerCharacter := newStr bitsPerCharacter.
 
     1 to:mySize do:[:i |
-        c := (self at:i) asUppercase.
-        c bitsPerCharacter > bitsPerCharacter ifTrue:[
-            newStr := c stringSpecies fromString:newStr.
-        ].
-        newStr at:i put:c
+	c := (self at:i) asUppercase.
+	c bitsPerCharacter > bitsPerCharacter ifTrue:[
+	    newStr := c stringSpecies fromString:newStr.
+	].
+	newStr at:i put:c
     ].
     ^ newStr
 
@@ -2686,13 +2689,13 @@
     tmpStream := WriteStream on:(self class new).
     idx := 1.
     [idx ~~ 0] whileTrue:[
-        idx1 := idx.
-        idx := self indexOfSubCollection:subString startingAt:idx.
-        idx ~~ 0 ifTrue:[
-            tmpStream nextPutAll:(self copyFrom:idx1 to:idx-1).
-            tmpStream nextPutAll:newString.
-            idx := idx + subString size
-        ]
+	idx1 := idx.
+	idx := self indexOfSubCollection:subString startingAt:idx.
+	idx ~~ 0 ifTrue:[
+	    tmpStream nextPutAll:(self copyFrom:idx1 to:idx-1).
+	    tmpStream nextPutAll:newString.
+	    idx := idx + subString size
+	]
     ].
     tmpStream nextPutAll:(self copyFrom:idx1).
     ^ tmpStream contents
@@ -2703,7 +2706,7 @@
      '12345678901234567890' copyReplaceString:'234' withString:'foo'
 
      ('a string with spaces' copyReplaceAll:$  withAll:' foo ')
-        copyReplaceString:'foo' withString:'bar'
+	copyReplaceString:'foo' withString:'bar'
     "
 
     "Modified: / 31-05-1999 / 12:33:59 / cg"
@@ -3188,8 +3191,8 @@
     |matchers|
 
     matchers := self asCollectionOfSubstringsSeparatedBy:$;.
-    ^ matchers contains:[:aPattern | 
-        aPattern match:aString ignoreCase:ignoreCase escapeCharacter:nil
+    ^ matchers contains:[:aPattern |
+	aPattern match:aString ignoreCase:ignoreCase escapeCharacter:nil
       ].
 
 "/    matchers do:[:aPattern |
@@ -3204,9 +3207,9 @@
      'f*;b*' match:'bar'
      'f*;b*' compoundMatch:'foo'
      'f*;b*' compoundMatch:'bar'
-     'f*;b*' compoundMatch:'Foo' ignoreCase:true 
-     'f*;b*' compoundMatch:'Bar' ignoreCase:true 
-     'f*;b*' compoundMatch:'ccc' ignoreCase:true  
+     'f*;b*' compoundMatch:'Foo' ignoreCase:true
+     'f*;b*' compoundMatch:'Bar' ignoreCase:true
+     'f*;b*' compoundMatch:'ccc' ignoreCase:true
     "
 
     "Modified: / 15.4.1997 / 15:50:33 / cg"
@@ -3314,19 +3317,19 @@
     ^ (self findMatchString:matchString startingAt:1 ignoreCase:caseSensitive not ifAbsent:0) ~~ 0
 
     "
-     '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:'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  
+     'hello world' includesMatchString:'woR*' caseSensitive:true
+     'hello world' includesMatchString:'woR*' caseSensitive:false
     "
 !
 
@@ -3337,7 +3340,7 @@
      Lower/uppercase are considered different.
      The escape character is the backQuaote.
      NOTICE: match-meta character interpretation is like in unix-matching,
-             NOT the ST-80 meaning."
+	     NOT the ST-80 meaning."
 
     ^ self match:aString from:1 to:aString size ignoreCase:false
 
@@ -3366,7 +3369,7 @@
      or [...] to match a set of characters.
      Lower/uppercase are considered different.
      NOTICE: match-meta character interpretation is like in unix-matching,
-             NOT the ST-80 meaning."
+	     NOT the ST-80 meaning."
 
     ^ self match:aString from:1 to:aString size ignoreCase:false escapeCharacter:escape
 
@@ -3384,11 +3387,11 @@
      If ignoreCase is true, lower/uppercase are considered the same.
      The escape character is the backQuaote.
      NOTICE: match-meta character interpretation is like in unix-matching,
-             NOT the ST-80 meaning."
-
-    ^ self 
-        match:aString from:start to:stop ignoreCase:ignoreCase
-        escapeCharacter:(self class matchEscapeCharacter)
+	     NOT the ST-80 meaning."
+
+    ^ self
+	match:aString from:start to:stop ignoreCase:ignoreCase
+	escapeCharacter:(self class matchEscapeCharacter)
 
     "
      '*ute*' match:'12345COMPUTER' from:1 to:5 ignoreCase:true
@@ -3405,7 +3408,7 @@
      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,
-             NOT the ST-80 meaning."
+	     NOT the ST-80 meaning."
 
     |matchScanArray|
 
@@ -3416,23 +3419,23 @@
     "
     (PreviousMatch notNil
     and:[PreviousMatch key = self]) ifTrue:[
-        matchScanArray := PreviousMatch value
+	matchScanArray := PreviousMatch value
     ] ifFalse:[
-        matchScanArray := self class matchScanArrayFrom:self escapeCharacter:escape.
-        matchScanArray isNil ifTrue:[
-            'CharacterArray [info]: invalid matchpattern:''' infoPrint. self infoPrint. ''' comparing for equality.' infoPrintCR.
-            ^ self = aString
+	matchScanArray := self class matchScanArrayFrom:self escapeCharacter:escape.
+	matchScanArray isNil ifTrue:[
+	    'CharacterArray [info]: invalid matchpattern:''' infoPrint. self infoPrint. ''' comparing for equality.' infoPrintCR.
+	    ^ self = aString
 "/            ^ false
-        ].
-        PreviousMatch := self -> matchScanArray.
+	].
+	PreviousMatch := self -> matchScanArray.
     ].
 
     ^ self class
-        matchScan:matchScanArray
-        from:1 to:matchScanArray size
-        with:aString
-        from:start to:stop
-        ignoreCase:ignoreCase
+	matchScan:matchScanArray
+	from:1 to:matchScanArray size
+	with:aString
+	from:start to:stop
+	ignoreCase:ignoreCase
 
     "
      '*ute*' match:'12345COMPUTER' from:1 to:5 ignoreCase:true
@@ -3449,7 +3452,7 @@
      If ignoreCase is true, lower/uppercase are considered the same.
      The escape character is the backQuaote.
      NOTICE: match-meta character interpretation is like in unix-matching,
-             NOT the ST-80 meaning."
+	     NOT the ST-80 meaning."
 
     ^ self match:aString from:1 to:aString size ignoreCase:ignoreCase
 
@@ -3466,14 +3469,14 @@
      '*some*compl*ern*' match:'this is another complicated pattern match' ignoreCase:true
 
      Time millisecondsToRun:[
-        Symbol allInstancesDo:[:sym |
-            '[ab]*' match:sym ignoreCase:false
-        ]
+	Symbol allInstancesDo:[:sym |
+	    '[ab]*' match:sym ignoreCase:false
+	]
      ].
      Time millisecondsToRun:[
-        Symbol allInstancesDo:[:sym |
-            '*at:*' match:sym ignoreCase:false
-        ]
+	Symbol allInstancesDo:[:sym |
+	    '*at:*' match:sym ignoreCase:false
+	]
      ].
     "
 
@@ -3486,7 +3489,7 @@
      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,
-             NOT the ST-80 meaning."
+	     NOT the ST-80 meaning."
 
     ^ self match:aString from:1 to:aString size ignoreCase:ignoreCase escapeCharacter:escape
 
@@ -3503,14 +3506,14 @@
      '*some*compl*ern*' match:'this is another complicated pattern match' ignoreCase:true
 
      Time millisecondsToRun:[
-        Symbol allInstancesDo:[:sym |
-            '[ab]*' match:sym ignoreCase:false
-        ]
+	Symbol allInstancesDo:[:sym |
+	    '[ab]*' match:sym ignoreCase:false
+	]
      ].
      Time millisecondsToRun:[
-        Symbol allInstancesDo:[:sym |
-            '*at:*' match:sym ignoreCase:false
-        ]
+	Symbol allInstancesDo:[:sym |
+	    '*at:*' match:sym ignoreCase:false
+	]
      ].
     "
 
@@ -3636,7 +3639,7 @@
     |string|
 
     (string := self string) ~~ self ifTrue:[
-        ^ string contains8BitCharacters
+	^ string contains8BitCharacters
     ].
     ^ self contains:[:aCharacter | aCharacter codePoint > 16r7F ].
 
@@ -3739,12 +3742,12 @@
     ^ Array with:nsPart with:selPart
 
     "test:
-     self assert:('+' nameSpaceSelectorParts) = #('' '+').         
-     self assert:(':+' nameSpaceSelectorParts) = #('' ':+').           
-     self assert:(':Foo:+' nameSpaceSelectorParts) = #('' ':Foo:+').       
-
-     self assert:(':Foo::+' nameSpaceSelectorParts) = #('Foo' '+').   
-     self assert:(':Foo::bar:baz:' nameSpaceSelectorParts) = #('Foo' 'bar:baz:'). 
+     self assert:('+' nameSpaceSelectorParts) = #('' '+').
+     self assert:(':+' nameSpaceSelectorParts) = #('' ':+').
+     self assert:(':Foo:+' nameSpaceSelectorParts) = #('' ':Foo:+').
+
+     self assert:(':Foo::+' nameSpaceSelectorParts) = #('Foo' '+').
+     self assert:(':Foo::bar:baz:' nameSpaceSelectorParts) = #('Foo' 'bar:baz:').
     "
 
     "Created: / 05-03-2007 / 17:16:58 / cg"
@@ -3804,14 +3807,14 @@
 
     n1 := n2 := maxLen // 2.
     maxLen odd ifTrue:[
-        n2 := n1 + 1
+	n2 := n1 + 1
     ].
     ^ (self copyFrom:1 to:n1) , (self copyFrom:sz - n2 + 1)
 
     "
      '12345678901234'   chopTo:15
-     '123456789012345'  chopTo:15       
-     '1234567890123456' chopTo:15       
+     '123456789012345'  chopTo:15
+     '1234567890123456' chopTo:15
      'aShortString' chopTo:15
      'aVeryLongNameForAStringThatShouldBeShortened' chopTo:15
     "
@@ -3833,8 +3836,8 @@
 
     "
      '12345678901234' contractAtBeginningTo:15
-     '123456789012345' contractAtBeginningTo:15  
-     '1234567890123456' contractAtBeginningTo:15 
+     '123456789012345' contractAtBeginningTo:15
+     '1234567890123456' contractAtBeginningTo:15
      'aShortString' contractAtBeginningTo:15
      'aVeryLongNameForAStringThatShouldBeShortened' contractAtBeginningTo:15
     "
@@ -3855,9 +3858,9 @@
     ^ (self copyTo:maxLen-3),'...'
 
     "
-     '12345678901234' contractAtEndTo:15     
-     '123456789012345' contractAtEndTo:15    
-     '1234567890123456' contractAtEndTo:15   
+     '12345678901234' contractAtEndTo:15
+     '123456789012345' contractAtEndTo:15
+     '1234567890123456' contractAtEndTo:15
      'aShortString' contractAtEndTo:15
      'aVeryLongNameForAStringThatShouldBeShortened' contractAtEndTo:15
     "
@@ -3881,17 +3884,17 @@
     leftEnd := halfSize-1.
     rightStart := sz-halfSize+2.
     halfSize even ifTrue:[
-        rightStart := rightStart+1.
-    ].        
+	rightStart := rightStart+1.
+    ].
     ^ (self copyTo:leftEnd),'...',(self copyFrom:rightStart)
 
     "
-     '12345678901234' contractTo:15        
-     '123456789012345' contractTo:15       
-     '1234567890123456' contractTo:15       
-     'aShortString' contractTo:15                                                                                        
-     'aVeryLongNameForAStringThatShouldBeShortened' contractTo:15                                             
-     'C:\Dokumente und Einstellungen\cg\work\bosch\dapas\hw_schnittstellen\DAPAS__HpibDLL.st' contractTo:40  
+     '12345678901234' contractTo:15
+     '123456789012345' contractTo:15
+     '1234567890123456' contractTo:15
+     'aShortString' contractTo:15
+     'aVeryLongNameForAStringThatShouldBeShortened' contractTo:15
+     'C:\Dokumente und Einstellungen\cg\work\bosch\dapas\hw_schnittstellen\DAPAS__HpibDLL.st' contractTo:40
     "
 
     "Modified: / 24-10-2006 / 12:23:56 / cg"
@@ -3921,54 +3924,54 @@
     stop := self size.
     start := 1.
     [start <= stop] whileTrue:[
-        idx := self indexOf:$% startingAt:start.
-        (idx == 0 or:[idx == stop]) ifTrue:[
-            ^ expandedString , (self copyFrom:start to:stop)
-        ].
-        "found a %"
-        expandedString := expandedString , (self copyFrom:start to:(idx - 1)).
-        next := self at:(idx + 1).
-        (next == $%) ifTrue:[
-            expandedString := expandedString , '%'
-        ] ifFalse:[
-            (next between:$1 and:$9) ifTrue:[
-                v := argArrayOrDictionary at:(next digitValue) ifAbsent:nil
-            ] ifFalse:[
-                next == $( ifTrue:[
-                    idx2 := self indexOf:$) startingAt:idx+2.
-                    key := self copyFrom:idx+2 to:idx2-1.
-                    idx := idx2 - 1.
-                    keyAsSymbol := key asSymbolIfInterned.
-                    (keyAsSymbol notNil and:[ argArrayOrDictionary includesKey:keyAsSymbol ]) ifTrue:[
-                        v := argArrayOrDictionary at:keyAsSymbol
-                    ] ifFalse:[
-                        (key conform:[:each | each isDigit]) ifTrue:[
-                            key := Number readFrom:key onError:nil.
-                        ].
-                        v := argArrayOrDictionary at:key ifAbsent:nil
-                    ].
-                ] ifFalse:[
-                    argArrayOrDictionary isSequenceable ifFalse:[
-                        "Arrays etc. can be only indexed with integers, not with characters or strings"
-                        v := argArrayOrDictionary at:next ifAbsent:nil.
-                        v isNil ifTrue:[
-                            v := argArrayOrDictionary at:next asString asSymbol ifAbsent:nil.
-                        ].
-                    ].
-                    v isNil ifTrue:[
-                        v := String with:$% with:next. "No match, keep original sequence"
-                    ].
-                ]
-            ].
-            v isNil
-                ifTrue:[v := '']
-                ifFalse:[
-                    v isBlock ifTrue:[
-                        v := v value
-                    ]].
-            expandedString := expandedString , v printString
-        ].
-        start := idx + 2
+	idx := self indexOf:$% startingAt:start.
+	(idx == 0 or:[idx == stop]) ifTrue:[
+	    ^ expandedString , (self copyFrom:start to:stop)
+	].
+	"found a %"
+	expandedString := expandedString , (self copyFrom:start to:(idx - 1)).
+	next := self at:(idx + 1).
+	(next == $%) ifTrue:[
+	    expandedString := expandedString , '%'
+	] ifFalse:[
+	    (next between:$1 and:$9) ifTrue:[
+		v := argArrayOrDictionary at:(next digitValue) ifAbsent:nil
+	    ] ifFalse:[
+		next == $( ifTrue:[
+		    idx2 := self indexOf:$) startingAt:idx+2.
+		    key := self copyFrom:idx+2 to:idx2-1.
+		    idx := idx2 - 1.
+		    keyAsSymbol := key asSymbolIfInterned.
+		    (keyAsSymbol notNil and:[ argArrayOrDictionary includesKey:keyAsSymbol ]) ifTrue:[
+			v := argArrayOrDictionary at:keyAsSymbol
+		    ] ifFalse:[
+			(key conform:[:each | each isDigit]) ifTrue:[
+			    key := Number readFrom:key onError:nil.
+			].
+			v := argArrayOrDictionary at:key ifAbsent:nil
+		    ].
+		] ifFalse:[
+		    argArrayOrDictionary isSequenceable ifFalse:[
+			"Arrays etc. can be only indexed with integers, not with characters or strings"
+			v := argArrayOrDictionary at:next ifAbsent:nil.
+			v isNil ifTrue:[
+			    v := argArrayOrDictionary at:next asString asSymbol ifAbsent:nil.
+			].
+		    ].
+		    v isNil ifTrue:[
+			v := String with:$% with:next. "No match, keep original sequence"
+		    ].
+		]
+	    ].
+	    v isNil
+		ifTrue:[v := '']
+		ifFalse:[
+		    v isBlock ifTrue:[
+			v := v value
+		    ]].
+	    expandedString := expandedString , v printString
+	].
+	start := idx + 2
     ].
     ^  expandedString
 
@@ -4000,9 +4003,9 @@
     ^ self asCollectionOfSubCollectionsSeparatedBy:Character cr do:[:line | ^ line].
 
     "
-     'hello' firstLine   
-     '1\2\3' withCRs firstLine   
-     '\1\2\3' withCRs firstLine   
+     'hello' firstLine
+     '1\2\3' withCRs firstLine
+     '\1\2\3' withCRs firstLine
     "
 !
 
@@ -4453,17 +4456,17 @@
 
     result := self.
     ((result startsWith:$") or:[(result startsWith:$')]) ifTrue:[
-        quote := result at:1.
-        result := result copyFrom:2.
-        (result endsWith:quote) ifTrue:[
-            result := result copyWithoutLast:1
-        ].
+	quote := result at:1.
+	result := result copyFrom:2.
+	(result endsWith:quote) ifTrue:[
+	    result := result copyWithoutLast:1
+	].
     ].
     ^ result
 
-"/    '"hello"' withoutQuotes   
-"/    '''hello''' withoutQuotes 
-"/    'hello' withoutQuotes 
+"/    '"hello"' withoutQuotes
+"/    '''hello''' withoutQuotes
+"/    'hello' withoutQuotes
 !
 
 withoutSeparators
@@ -4655,46 +4658,46 @@
      startIndex "{ Class: SmallInteger }"
      subSize    "{ Class: SmallInteger }"
      mySize     "{ Class: SmallInteger }"
-     runIdx     "{ Class: SmallInteger }" 
+     runIdx     "{ Class: SmallInteger }"
      tester|
 
     subSize := subString size.
     subSize == 0 ifTrue:[   "empty string matches"
-        subString isString ifFalse:[
-           self error:'non string argument' mayProceed:true.
-        ].
-        ^ index
+	subString isString ifFalse:[
+	   self error:'non string argument' mayProceed:true.
+	].
+	^ index
     ].
     tester := caseSensitive ifTrue:[ [:c1 :c2 | c1 = c2 ] ] ifFalse:[ [:c1 :c2 | c1 sameAs: c2 ] ].
 
     mySize := self size.
     firstChar := subString at:1.
     caseSensitive ifTrue:[
-        startIndex := self indexOf:firstChar startingAt:index.
+	startIndex := self indexOf:firstChar startingAt:index.
     ] ifFalse:[
-        startIndex := self findFirst:[:c | c sameAs:firstChar] startingAt:index.
+	startIndex := self findFirst:[:c | c sameAs:firstChar] startingAt:index.
     ].
     [startIndex == 0] whileFalse:[
-        runIdx := startIndex.
-        found := true.
-        1 to:subSize do:[:i |
-            runIdx > mySize ifTrue:[
-                found := false
-            ] ifFalse:[
-                (tester value:(subString at:i) value:(self at:runIdx)) ifFalse:[
-                    found := false
-                ]
-            ].
-            runIdx := runIdx + 1
-        ].
-        found ifTrue:[
-            ^ startIndex
-        ].
-        caseSensitive ifTrue:[
-            startIndex := self indexOf:firstChar startingAt:(startIndex + 1)
-        ] ifFalse:[
-            startIndex := self findFirst:[:c | c sameAs:firstChar] startingAt:(startIndex + 1).
-        ].
+	runIdx := startIndex.
+	found := true.
+	1 to:subSize do:[:i |
+	    runIdx > mySize ifTrue:[
+		found := false
+	    ] ifFalse:[
+		(tester value:(subString at:i) value:(self at:runIdx)) ifFalse:[
+		    found := false
+		]
+	    ].
+	    runIdx := runIdx + 1
+	].
+	found ifTrue:[
+	    ^ startIndex
+	].
+	caseSensitive ifTrue:[
+	    startIndex := self indexOf:firstChar startingAt:(startIndex + 1)
+	] ifFalse:[
+	    startIndex := self findFirst:[:c | c sameAs:firstChar] startingAt:(startIndex + 1).
+	].
     ].
     ^ exceptionBlock value
 
@@ -4822,18 +4825,18 @@
      i.e. consists of a letter followed by letters or digits."
 
     self size == 0 ifTrue:[
-        "mhmh what is this ?"
-        ^ false
+	"mhmh what is this ?"
+	^ false
     ].
     (self at:1) isLetter ifFalse:[^ false].
     ^ self conform:[:char | char isLetterOrDigit].
 
     "
-     'helloWorld' isAlphaNumeric 
-     'foo1234' isAlphaNumeric    
-     'f1234' isAlphaNumeric      
-     '1234' isAlphaNumeric       
-     '+' isAlphaNumeric          
+     'helloWorld' isAlphaNumeric
+     'foo1234' isAlphaNumeric
+     'f1234' isAlphaNumeric
+     '1234' isAlphaNumeric
+     '+' isAlphaNumeric
     "
 
     "Modified: / 13-10-2006 / 12:53:49 / cg"
@@ -4872,10 +4875,10 @@
     ^ (self contains:[:char | char ~~ Character space]) not
 
     "
-     '' isBlank  
-     '   a    ' isBlank  
-     '        ' isBlank  
-     '        ' asUnicode16String isBlank  
+     '' isBlank
+     '   a    ' isBlank
+     '        ' isBlank
+     '        ' asUnicode16String isBlank
     "
 !
 
@@ -4897,12 +4900,12 @@
     ^ true
 
     "test:
-     self assert:('+' isNameSpaceSelector) not.         
-     self assert:(':+' isNameSpaceSelector) not.           
-     self assert:(':Foo:+' isNameSpaceSelector) not.       
-
-     self assert:(':Foo::+' isNameSpaceSelector).   
-     self assert:(':Foo::bar:baz:' isNameSpaceSelector). 
+     self assert:('+' isNameSpaceSelector) not.
+     self assert:(':+' isNameSpaceSelector) not.
+     self assert:(':Foo:+' isNameSpaceSelector) not.
+
+     self assert:(':Foo::+' isNameSpaceSelector).
+     self assert:(':Foo::bar:baz:' isNameSpaceSelector).
     "
 
     "Created: / 05-03-2007 / 11:35:31 / cg"
@@ -4913,7 +4916,7 @@
      i.e. consists only of digits."
 
     self size == 0 ifTrue:[
-        ^ false
+	^ false
     ].
     ^ self conform:[:char | char isDigit]
 
@@ -4951,13 +4954,13 @@
     ^ self first isUppercase
 
     "
-     '' isUppercaseFirst       
-     'a' isUppercaseFirst      
-     'A' isUppercaseFirst      
-     'aaaaa' isUppercaseFirst  
-     'Aaaaa' isUppercaseFirst  
-     'aaaaAaaaa' isUppercaseFirst 
-     '12345' isUppercaseFirst     
+     '' isUppercaseFirst
+     'a' isUppercaseFirst
+     'A' isUppercaseFirst
+     'aaaaa' isUppercaseFirst
+     'Aaaaa' isUppercaseFirst
+     'aaaaAaaaa' isUppercaseFirst
+     '12345' isUppercaseFirst
     "
 !
 
@@ -5107,26 +5110,26 @@
     |binopChars|
 
     (self size <= Scanner maxBinarySelectorSize) ifTrue:[
-        binopChars := Scanner binarySelectorCharacters.
-        (self conform:[:eachChar | (binopChars includes:eachChar)]) ifTrue:[
-            ^ 1
-        ].
+	binopChars := Scanner binarySelectorCharacters.
+	(self conform:[:eachChar | (binopChars includes:eachChar)]) ifTrue:[
+	    ^ 1
+	].
     ].
     ^ self occurrencesOf:$:
 
     "
-     'foo:bar:' numArgs 
-     #foo:bar: numArgs  
-     'hello' numArgs    
-     '+' numArgs        
-     '++' numArgs       
-     '+++' numArgs      
-     '|' numArgs        
-     '?' numArgs        
-     '_' numArgs        
-     '_:' numArgs        
-     '_:_:' numArgs        
-     '<->' numArgs        
+     'foo:bar:' numArgs
+     #foo:bar: numArgs
+     'hello' numArgs
+     '+' numArgs
+     '++' numArgs
+     '+++' numArgs
+     '|' numArgs
+     '?' numArgs
+     '_' numArgs
+     '_:' numArgs
+     '_:_:' numArgs
+     '<->' numArgs
     "
 
     "Modified: / 13-10-2006 / 11:52:33 / cg"
@@ -5254,7 +5257,7 @@
 !CharacterArray class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.361 2007-09-07 12:54:01 sr Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.362 2007-09-10 11:43:47 stefan Exp $'
 ! !
 
 CharacterArray initialize!