CharacterArray.st
changeset 154 d4236ec280a6
parent 138 c9f46b635f98
child 163 9868f2750ba5
--- a/CharacterArray.st	Thu Sep 29 21:38:11 1994 +0100
+++ b/CharacterArray.st	Mon Oct 10 01:20:00 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -19,9 +19,9 @@
 
 AbstractString comment:'
 COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.7 1994-08-23 23:06:41 claus Exp $
+$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.8 1994-10-10 00:19:39 claus Exp $
 '!
 
 !AbstractString class methodsFor:'documentation'!
@@ -29,7 +29,7 @@
 copyright
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.7 1994-08-23 23:06:41 claus Exp $
+$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.8 1994-10-10 00:19:39 claus Exp $
 "
 !
 
@@ -50,6 +50,10 @@
 "
     AbstractString is a superclass for all kinds of Strings (i.e.
     (singleByte-)Strings, TwoByteStrings and whatever comes in the future.
+
+    As the name already implies, this class is abstract, meaning that there are
+    no instances of it. All this class does is provide common protocol for 
+    concrete subclasses.
 "
 ! !
 
@@ -86,7 +90,7 @@
     mySize := self size.
     newStr := self species new:mySize.
     1 to:mySize do:[:i |
-        newStr at:i put:(self at:i) asUppercase
+	newStr at:i put:(self at:i) asUppercase
     ].
     ^newStr
 !
@@ -100,7 +104,7 @@
     mySize := self size.
     newStr := self species new:mySize.
     1 to:mySize do:[:i |
-        newStr at:i put:(self at:i) asLowercase
+	newStr at:i put:(self at:i) asLowercase
     ].
     ^newStr
 !
@@ -126,14 +130,16 @@
 asText
     "return a Text-object (collection of lines) from myself.
      BIG warning: Text is totally misnamed here 
-         - ST/X's Text has nothing to do with PP's Text.
-         Therefore it will be removed/renamed soon."
+     - ST/X's Text has nothing to do with PP's Text.
+     Therefore it will be removed/renamed soon."
 
     ^ Text from:self
 !
 
 asNumber
-    "read a number from the receiver"
+    "read a number from the receiver.
+     Notice, that errors may occur during the read, so you better
+     setup some signal handler when using this method."
 
     ^ Number readFromString:self
 
@@ -141,11 +147,15 @@
      '123'     asNumber
      '123.567' asNumber
      '(5/6)'   asNumber
+     'foo'     asNumber
+     Object errorSignal handle:[:ex | ex returnWith:0] do:['foo' asNumber] 
     "
 !
 
 asInteger
-    "read an integer from the receiver"
+    "read an integer from the receiver.
+     Notice, that errors may occur during the read, so you better
+     setup some signal handler when using this method."
 
     ^ Integer readFromString:self
 
@@ -154,11 +164,14 @@
      '-1234' asInteger
      '0.123' asInteger   <- reader stops at ., returning 0 here
      '0.123' asNumber    <- returns what you expect
+     Object errorSignal handle:[:ex | ex returnWith:0] do:['foo' asInteger] 
     "
 !
 
 asFloat
-    "read an float from the receiver"
+    "read a float number from the receiver.
+     Notice, that errors may occur during the read, so you better
+     setup some signal handler when using this method."
 
     ^ (Number readFromString:self) asFloat
 
@@ -166,6 +179,7 @@
      '0.123' asFloat 
      '12345' asFloat
      '(1/5)' asFloat
+     Object errorSignal handle:[:ex | ex returnWith:0] do:['foo' asFloat] 
     "
 !
 
@@ -177,9 +191,10 @@
 
 asCollectionOfWords
     "return a collection containing the words (separated by whitespace) 
-     of the receiver"
+     of the receiver. Multiple occurences of whitespace characters will
+     be treated like one - i.e. whitespace is skipped."
 
-    |words ch
+    |words
      start  "{ Class:SmallInteger }" 
      stop   "{ Class:SmallInteger }" 
      mySize "{ Class:SmallInteger }"|
@@ -188,30 +203,17 @@
     start := 1.
     mySize := self size.
     [start <= mySize] whileTrue:[
-        start := self indexOfNonSeparatorStartingAt:start.
-        start == 0 ifTrue:[
-            ^ words
-        ].
-        stop := self indexOfSeparatorStartingAt:start.
-        stop == 0 ifTrue:[
-            words add:(self copyFrom:start to:mySize).
-            ^ words
-        ].
-        words add:(self copyFrom:start to:(stop - 1)).
-        start := stop
-
-"/        ch := self at:start.
-"/        ((ch == Character space) or:[ch isSeparator]) ifTrue:[
-"/            start := start + 1
-"/        ] ifFalse:[
-"/            stop := self indexOfSeparatorStartingAt:start.
-"/            stop == 0 ifTrue:[
-"/                words add:(self copyFrom:start to:mySize).
-"/                ^ words
-"/            ].
-"/            words add:(self copyFrom:start to:(stop - 1)).
-"/            start := stop
-"/        ]
+	start := self indexOfNonSeparatorStartingAt:start.
+	start == 0 ifTrue:[
+	    ^ words
+	].
+	stop := self indexOfSeparatorStartingAt:start.
+	stop == 0 ifTrue:[
+	    words add:(self copyFrom:start to:mySize).
+	    ^ words
+	].
+	words add:(self copyFrom:start to:(stop - 1)).
+	start := stop
     ].
     ^ words
 
@@ -224,9 +226,10 @@
     "
 !
 
-asCollectionOfLines
-    "return a collection containing the lines (separated by cr) 
-     of the receiver."
+asCollectionOfSubstringsSeparatedBy:aCharacter
+    "return a collection containing the lines (separated by aCharacter) 
+     of the receiver. If aCharacter occurs multiple times in a row, 
+     the result will contain empty strings."
 
     |lines myClass
      numberOfLines "{ Class:SmallInteger }"
@@ -235,37 +238,50 @@
 
     "count first, to avoid regrowing"
 
-    numberOfLines := (self occurrencesOf:Character cr) + 1.
+    numberOfLines := (self occurrencesOf:aCharacter) + 1.
     lines := OrderedCollection new:numberOfLines.
     myClass := self species.
 
     startIndex := 1.
     1 to:numberOfLines do:[:lineNr |
-        stopIndex := self indexOf:(Character cr) startingAt:startIndex.
-        stopIndex == 0 ifTrue:[
-            stopIndex := self size
-        ] ifFalse: [
-            stopIndex := stopIndex - 1.
-        ].
+	stopIndex := self indexOf:aCharacter startingAt:startIndex.
+	stopIndex == 0 ifTrue:[
+	    stopIndex := self size
+	] ifFalse: [
+	    stopIndex := stopIndex - 1.
+	].
 
-        (stopIndex < startIndex) ifTrue: [
-            lines add:(myClass new:0)
-        ] ifFalse: [
-            lines add:(self copyFrom:startIndex to:stopIndex)
-        ].
-        startIndex := stopIndex + 2
+	(stopIndex < startIndex) ifTrue: [
+	    lines add:(myClass new:0)
+	] ifFalse: [
+	    lines add:(self copyFrom:startIndex to:stopIndex)
+	].
+	startIndex := stopIndex + 2
     ].
     ^ lines
 
     "
+     '1 one:2 two:3 three:4 four:5 five' withCRs asCollectionOfSubstringsSeparatedBy:$: 
+     '1 one 2 two 3 three 4 four 5 five' withCRs asCollectionOfSubstringsSeparatedBy:Character space
+    "
+!
+
+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."
+
+    ^ self asCollectionOfSubstringsSeparatedBy:Character cr
+
+    "
      '1 one\2 two\3 three\4 four\5 five' withCRs asCollectionOfLines
-     '1 one\2 two\3 three\4 four\5 five' withCRs asCollectionOfWords
+     '1 one\\\\2 two\3 three' withCRs asCollectionOfLines  
     "
 !
 
 asArrayOfSubstrings
     "return an array of substrings from the receiver, interpreting
-     separators (i.e. spaces & newlines) as work-delimiters.
+     separators (i.e. spaces & newlines) as word-delimiters.
      This is a compatibility method - the actual work is done in
      asCollectionOfWords."
 
@@ -274,13 +290,53 @@
     "
      '1 one two three four 5 five' asArrayOfSubstrings  
     "
+!
+
+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."
+
+    |words
+     start  "{ Class:SmallInteger }" 
+     stop   "{ Class:SmallInteger }" 
+     mySize "{ Class:SmallInteger }"|
+
+    words := OrderedCollection new.
+    start := 1.
+    mySize := self size.
+    [start <= mySize] whileTrue:[
+	"skip multiple separators"
+	[aCollectionOfSeparators includes:(self at:start)] whileTrue:[
+	    start := start + 1 .
+	    start > mySize ifTrue:[
+		^ words
+	    ].
+	].
+
+	stop := self indexOfAny:aCollectionOfSeparators startingAt:start.
+	stop == 0 ifTrue:[
+	    words add:(self copyFrom:start to:mySize).
+	    ^ words
+	].
+	words add:(self copyFrom:start to:(stop - 1)).
+	start := stop
+    ].
+    ^ words
+
+    "
+     'hello:world:isnt:this nice' asCollectionOfSubstringsSeparatedByAny:#($:)
+     'hello:world:isnt:this nice' asCollectionOfSubstringsSeparatedByAny:(Array with:$: with:Character space) 
+     'h1e2l3l4o' asCollectionOfSubstringsSeparatedByAny:($1 to: $9) 
+    "
 ! !
 
 !AbstractString methodsFor:'ST/V compatibility'!
 
 replChar:oldChar with:newChar
     "return a copy of the receiver, with all oldChars replaced
-     by newChar"
+     by newChar.
+     This is an ST/V compatibility method."
 
     ^ self copy replaceAll:oldChar by:newChar
 
@@ -291,17 +347,18 @@
 
 replChar:oldChar withString:newString
     "return a copy of the receiver, with all oldChars replaced
-     by newString (i.e. slice in the newString in place of the oldChar)"
+     by newString (i.e. slice in the newString in place of the oldChar).
+     This is an ST/V compatibility method."
 
     |tmpStream|
 
     tmpStream := WriteStream on:(self class new).
     self do:[:element |
-        element = oldChar ifTrue:[
-            tmpStream nextPutAll:newString
-        ] ifFalse:[
-            tmpStream nextPut:element 
-        ].
+	element = oldChar ifTrue:[
+	    tmpStream nextPutAll:newString
+	] ifFalse:[
+	    tmpStream nextPut:element 
+	].
     ].
     ^ tmpStream contents
 
@@ -313,7 +370,8 @@
 
 trimBlanks
     "return a copy of the receiver without leading
-     and trailing spaces"
+     and trailing spaces.
+     This is an ST/V compatibility method."
 
     ^ self withoutSpaces
 
@@ -326,11 +384,12 @@
 !
 
 byteAt:index put:aByte
-    "store a byte at given index"
+    "store a byte at given index.
+     This is an ST/V compatibility method."
 
     (aByte == 0) ifTrue:[
-        "store a space instead"
-        ^ super basicAt:index put:(Character space)
+	"store a space instead"
+	^ super basicAt:index put:(Character space)
     ].
     ^ super at:index put:(Character value:aByte)
 ! !
@@ -338,15 +397,15 @@
 !AbstractString methodsFor:'printing & storing'!
 
 article
-    "return an article string"
+    "return an article string for the receiver."
 
     |firstChar|
 
     firstChar := (self at:1) asLowercase. 
     (firstChar isVowel or:[firstChar == $x]) ifTrue:[
-        firstChar ~~ $u ifTrue:[
-             ^ 'an'
-        ]
+	firstChar ~~ $u ifTrue:[
+	     ^ 'an'
+	]
     ].
     ^ 'a'
 !
@@ -365,7 +424,7 @@
 
 displayString
     "return a string to display the receiver - use storeString to have
-     quotes around"
+     quotes around."
 
     ^ self storeString
 ! !
@@ -384,10 +443,10 @@
     cp = _stringVal(self);
     l = _stringSize(self);
     if (_qClass(self) != String) {
-        int n = __OBJS2BYTES__(_intVal(_ClassInstPtr(_qClass(self))->c_ninstvars));
+	int n = __OBJS2BYTES__(_intVal(_ClassInstPtr(_qClass(self))->c_ninstvars));
 
-        cp += n;
-        l -= n;
+	cp += n;
+	l -= n;
     }
 
     /*
@@ -396,15 +455,15 @@
      */
     val = 12345;
     for (cp0 = cp, cp += l - 1; cp >= cp0; cp--) {
-        val = (val << 5) + (*cp & 0x1F);
-        if (g = (val & 0x3E000000))
-            val ^= g >> 25 /* 23 */ /* 25 */;
-        val &= 0x3FFFFFFF;
+	val = (val << 5) + (*cp & 0x1F);
+	if (g = (val & 0x3E000000))
+	    val ^= g >> 25 /* 23 */ /* 25 */;
+	val &= 0x3FFFFFFF;
     }
 
     if (l) {
-        l |= 1; 
-        val = (val * l) & 0x3FFFFFFF;
+	l |= 1; 
+	val = (val * l) & 0x3FFFFFFF;
     }
 
     RETURN ( _MKSMALLINT(val) );
@@ -448,10 +507,10 @@
     otherSize := aString size.
 
     1 to:(mySize min:otherSize) do:[:index |
-        c1 := self at:index.
-        c2 := aString at:index.
-        c1 > c2 ifTrue:[^ true].
-        c1 < c2 ifTrue:[^ false].
+	c1 := self at:index.
+	c2 := aString at:index.
+	c1 > c2 ifTrue:[^ true].
+	c1 < c2 ifTrue:[^ false].
     ].
     ^ mySize > otherSize
 !
@@ -470,7 +529,7 @@
     mySize == otherSize ifFalse:[^ false].
 
     1 to:mySize do:[:index |
-        (self at:index) = (aString at:index) ifFalse:[^ false].
+	(self at:index) = (aString at:index) ifFalse:[^ false].
     ].
     ^ true
 
@@ -493,11 +552,11 @@
     mySize == otherSize ifFalse:[^ false].
 
     1 to:mySize do:[:index |
-        c1 := self at:index.
-        c2 := aString at:index.
-        c1 == c2 ifFalse:[
-            c1 asLowercase = c2 asLowercase ifFalse:[^ false].
-        ]
+	c1 := self at:index.
+	c2 := aString at:index.
+	c1 == c2 ifFalse:[
+	    c1 asLowercase = c2 asLowercase ifFalse:[^ false].
+	]
     ].
     ^ true
 
@@ -535,7 +594,7 @@
     mySize := self size.
 
     start to:mySize do:[:index |
-        (self at:index) isSeparator ifTrue:[^ index]
+	(self at:index) isSeparator ifTrue:[^ index]
     ].
     ^ 0
 
@@ -552,7 +611,7 @@
     mySize := self size.
 
     start to:mySize do:[:index |
-        (self at:index) isSeparator ifFalse:[^ index]
+	(self at:index) isSeparator ifFalse:[^ index]
     ].
     ^ 0
 
@@ -612,22 +671,22 @@
     firstChar := subString at:1.
     startIndex := self indexOf:firstChar startingAt:index.
     [startIndex == 0] whileFalse:[
-        runIdx := startIndex.
-        found := true.
-        1 to:subSize do:[:i |
-            runIdx > mySize ifTrue:[
-                found := false
-            ] ifFalse:[
-                (subString at:i) ~~ (self at:runIdx) ifTrue:[
-                    found := false
-                ]
-            ].
-            runIdx := runIdx + 1
-        ].
-        found ifTrue:[
-            ^ startIndex
-        ].
-        startIndex := self indexOf:firstChar startingAt:(startIndex + 1)
+	runIdx := startIndex.
+	found := true.
+	1 to:subSize do:[:i |
+	    runIdx > mySize ifTrue:[
+		found := false
+	    ] ifFalse:[
+		(subString at:i) ~~ (self at:runIdx) ifTrue:[
+		    found := false
+		]
+	    ].
+	    runIdx := runIdx + 1
+	].
+	found ifTrue:[
+	    ^ startIndex
+	].
+	startIndex := self indexOf:firstChar startingAt:(startIndex + 1)
     ].
     ^ exceptionBlock value
 ! !
@@ -659,104 +718,104 @@
     sStop := stop.
 
     [true] whileTrue:[
-        mSize := mStop - mStart + 1.
-        sSize := sStop - sStart + 1.
+	mSize := mStop - mStart + 1.
+	sSize := sStop - sStart + 1.
 
-        "empty strings match"
-        (mSize == 0) ifTrue:[^ (sSize == 0)].
+	"empty strings match"
+	(mSize == 0) ifTrue:[^ (sSize == 0)].
 
-        matchChar := self at:mStart.
+	matchChar := self at:mStart.
 
-        (matchChar == $#) ifTrue:[
-            "testString empty -> no match"
-            (sSize == 0) ifTrue:[^ false].
-            "# matches single character"
-            ((sSize == 1) and:[mSize == 1]) ifTrue:[^ true].
-            "cut off 1st chars and continue"
-            mStart := mStart + 1.
-            sStart := sStart + 1
-        ] ifFalse:[
-            (matchChar == $[) ifTrue:[
-                "testString empty -> no match"
-                (sSize == 0) ifTrue:[^ false].
+	(matchChar == $#) ifTrue:[
+	    "testString empty -> no match"
+	    (sSize == 0) ifTrue:[^ false].
+	    "# matches single character"
+	    ((sSize == 1) and:[mSize == 1]) ifTrue:[^ true].
+	    "cut off 1st chars and continue"
+	    mStart := mStart + 1.
+	    sStart := sStart + 1
+	] ifFalse:[
+	    (matchChar == $[) ifTrue:[
+		"testString empty -> no match"
+		(sSize == 0) ifTrue:[^ false].
 
-                matchSet := Set new.
-                c1 := nil.
-                [matchChar == $]] whileFalse:[
-                    mStart := mStart + 1.
-                    mSize := mSize - 1.
-                    matchChar := self at:mStart.
-                    ((matchChar == $-) and:[c1 notNil]) ifTrue:[
-                        mStart := mStart + 1.
-                        mSize := mSize - 1.
-                        c2 := self at:mStart.
-                        (c1 to:c2) do:[:c | matchSet add:c].
-                        c1 := nil
-                    ] ifFalse:[
-                        (matchChar == $]) ifFalse:[
-                            matchSet add:matchChar.
-                            c1 := matchChar.
-                        ].
-                    ].
-                ].
-                mStart := mStart + 1.
-                mSize := mSize - 1.
-                (matchSet includes:(aString at:sStart)) ifFalse:[^ false].
-                ((sSize == 1) and:[mSize == 0]) ifTrue:[^ true].
-                "cut off 1st char and continue"
-                sStart := sStart + 1
-            ] ifFalse:[
-                (matchChar == $*) ifTrue:[
-                    "* matches anything"
-                    (mSize == 1) ifTrue:[^ true].
-                    "testString empty -> matchString not we have no match"
-                    (sSize == 0) ifTrue:[^ false].
+		matchSet := Set new.
+		c1 := nil.
+		[matchChar == $]] whileFalse:[
+		    mStart := mStart + 1.
+		    mSize := mSize - 1.
+		    matchChar := self at:mStart.
+		    ((matchChar == $-) and:[c1 notNil]) ifTrue:[
+			mStart := mStart + 1.
+			mSize := mSize - 1.
+			c2 := self at:mStart.
+			(c1 to:c2) do:[:c | matchSet add:c].
+			c1 := nil
+		    ] ifFalse:[
+			(matchChar == $]) ifFalse:[
+			    matchSet add:matchChar.
+			    c1 := matchChar.
+			].
+		    ].
+		].
+		mStart := mStart + 1.
+		mSize := mSize - 1.
+		(matchSet includes:(aString at:sStart)) ifFalse:[^ false].
+		((sSize == 1) and:[mSize == 0]) ifTrue:[^ true].
+		"cut off 1st char and continue"
+		sStart := sStart + 1
+	    ] ifFalse:[
+		(matchChar == $*) ifTrue:[
+		    "* matches anything"
+		    (mSize == 1) ifTrue:[^ true].
+		    "testString empty -> matchString not we have no match"
+		    (sSize == 0) ifTrue:[^ false].
 
-                    "try to avoid some of the recursion by checking last
-                     character and continue with shortened strings if possible"
-                    cont := false.
-                    (mStop >= mStart) ifTrue:[
-                        matchLast := self at:mStop.
-                        (matchLast ~~ $*) ifTrue:[
-                            (matchLast == $#) ifTrue:[
-                                cont := true
-                            ] ifFalse:[
-                                (matchLast == (aString at:sStop)) ifTrue:[
-                                    cont := true
-                                ]
-                            ]
-                        ]
-                    ].
-                    cont ifFalse:[
-                        index := sStart.
-                        [index <= sStop] whileTrue:[
-                            (self from:(mStart + 1) to:mStop match:aString 
-                                  from:index to:sStop) ifTrue:[
-                                ^ true
-                            ].
-                            index := index + 1
-                        ].
-                        ^ false
-                    ].
-                    mStop := mStop - 1.
-                    sStop := sStop - 1
-                ] ifFalse:[
+		    "try to avoid some of the recursion by checking last
+		     character and continue with shortened strings if possible"
+		    cont := false.
+		    (mStop >= mStart) ifTrue:[
+			matchLast := self at:mStop.
+			(matchLast ~~ $*) ifTrue:[
+			    (matchLast == $#) ifTrue:[
+				cont := true
+			    ] ifFalse:[
+				(matchLast == (aString at:sStop)) ifTrue:[
+				    cont := true
+				]
+			    ]
+			]
+		    ].
+		    cont ifFalse:[
+			index := sStart.
+			[index <= sStop] whileTrue:[
+			    (self from:(mStart + 1) to:mStop match:aString 
+				  from:index to:sStop) ifTrue:[
+				^ true
+			    ].
+			    index := index + 1
+			].
+			^ false
+		    ].
+		    mStop := mStop - 1.
+		    sStop := sStop - 1
+		] ifFalse:[
 
-                    "testString empty ?"
-                    (sSize == 0) ifTrue:[^ false].
+		    "testString empty ?"
+		    (sSize == 0) ifTrue:[^ false].
 
-                    "first characters equal ?"
-                    ((aString at:sStart) ~~ matchChar) ifTrue:[^ false].
+		    "first characters equal ?"
+		    ((aString at:sStart) ~~ matchChar) ifTrue:[^ false].
 
-                    "avoid recursion if possible"
-                    ((sSize == mSize) and:[self = aString]) ifTrue:[^ true].
+		    "avoid recursion if possible"
+		    ((sSize == mSize) and:[self = aString]) ifTrue:[^ true].
 
-                    "cut off 1st chars and continue"
-                    mStart := mStart + 1.
-                    sStart := sStart + 1
-                ]
-            ]
-        ]
+		    "cut off 1st chars and continue"
+		    mStart := mStart + 1.
+		    sStart := sStart + 1
+		]
+	    ]
+	]
     ]
 !
 
@@ -784,11 +843,34 @@
     "return true, if the receiver contains spaces only"
 
     self do:[:char |
-        char ~~ Character space ifTrue:[^ false].
+	char ~~ Character space ifTrue:[^ false].
     ].
     ^ true
 !
 
+isAlphaNumeric
+    "return true, if the receiver is some alphanumeric word;
+     i.e. consists of a letter followed by letters or digits."
+
+    self size == 0 ifTrue:[
+	"mhmh what is this ?"
+	^ false
+    ].
+    (self at:1) isLetter ifFalse:[^ false].
+    self do:[:char |
+	char isLetterOrDigit ifFalse:[^ false].
+    ].
+    ^ true
+
+    "
+     'helloWorld' isAlphaNumeric  
+     'foo1234' isAlphaNumeric    
+     'f1234' isAlphaNumeric      
+     '1234' isAlphaNumeric       
+     '+' isAlphaNumeric         
+    "
+!
+
 countWords
     "return the number of words, which are separated by separators"
 
@@ -801,17 +883,17 @@
     start := 1.
     mySize := self size.
     [start <= mySize] whileTrue:[
-        ch := self at:start.
-        ch isSeparator ifTrue:[
-            start := start + 1
-        ] ifFalse:[
-            stop := self indexOfSeparatorStartingAt:start.
-            (stop == 0) ifTrue:[
-                stop := mySize + 1
-            ].
-            tally := tally + 1.
-            start := stop
-        ]
+	ch := self at:start.
+	ch isSeparator ifTrue:[
+	    start := start + 1
+	] ifFalse:[
+	    stop := self indexOfSeparatorStartingAt:start.
+	    (stop == 0) ifTrue:[
+		stop := mySize + 1
+	    ].
+	    tally := tally + 1.
+	    start := stop
+	]
     ].
     ^ tally
 
@@ -820,28 +902,28 @@
     "
 !
 
-nArgsIfSelector
+numArgs
     "treating the receiver as a message selector, return how many arguments would it take"
 
     |binopChars|
 
     (self size > 2) ifFalse:[
-        binopChars := '|&-+=*/\<>~@,'.
-        (self size == 1) ifTrue:[
-            ((binopChars occurrencesOf:(self at:1)) == 0) ifTrue:[^ 0].
-            ^ 1
-        ].
-        ((binopChars occurrencesOf:(self at:1)) == 0) ifFalse:[
-            ((binopChars occurrencesOf:(self at:2)) == 0) ifFalse:[^ 1]
-        ]
+	binopChars := '|&-+=*/\<>~@,'.
+	(self size == 1) ifTrue:[
+	    ((binopChars occurrencesOf:(self at:1)) == 0) ifTrue:[^ 0].
+	    ^ 1
+	].
+	((binopChars occurrencesOf:(self at:1)) == 0) ifFalse:[
+	    ((binopChars occurrencesOf:(self at:2)) == 0) ifFalse:[^ 1]
+	]
     ].
     ^ self occurrencesOf:$:
 
     "
-     'foo:bar:' nArgsIfSelector  
-     #foo:bar: nArgsIfSelector    
-     'hello' nArgsIfSelector       
-     '+' nArgsIfSelector   
+     'foo:bar:' numArgs  
+     #foo:bar: numArgs    
+     'hello' numArgs       
+     '+' numArgs   
     "
 !
 
@@ -855,13 +937,13 @@
     idx1 := 1.
     sz := self size.
     [true] whileTrue:[
-        idx2 := self indexOf:$: startingAt:idx1 + 1.
-        (idx2 == 0 or:[idx2 == sz]) ifTrue:[
-            coll add:(self copyFrom:idx1).
-            ^ coll
-        ].
-        coll add:(self copyFrom:idx1 to:idx2).
-        idx1 := idx2 + 1
+	idx2 := self indexOf:$: startingAt:idx1 + 1.
+	(idx2 == 0 or:[idx2 == sz]) ifTrue:[
+	    coll add:(self copyFrom:idx1).
+	    ^ coll
+	].
+	coll add:(self copyFrom:idx1 to:idx2).
+	idx1 := idx2 + 1
     ].
 
     "
@@ -879,6 +961,14 @@
      see IEEE transactions on Computers 1976 Pg 172 ff."
 
     ^ self levenshteinTo:aString s:4 c:1 i:2 d:6
+
+    "
+     'ocmprt' levenshteinTo:'computer'
+     'computer' levenshteinTo:'computer'
+     'ocmputer' levenshteinTo:'computer'
+     'cmputer' levenshteinTo:'computer'
+     'Computer' levenshteinTo:'computer'
+    "
 !
 
 levenshteinTo:aString s:substWeight c:caseWeight i:insrtWeight d:deleteWeight
@@ -899,7 +989,7 @@
 
     d := Array new:dimPlus1.
     1 to:dimPlus1 do:[:i |
-        d at:i put:(Array new:dimPlus1)
+	d at:i put:(Array new:dimPlus1)
     ].
 
     "init help-matrix"
@@ -907,51 +997,50 @@
     (d at:1) at:1 put:0.
     row := d at:1.
     1 to:dim do:[:j |
-        row at:(j + 1) put:( (row at:j) + insrtWeight )
+	row at:(j + 1) put:( (row at:j) + insrtWeight )
     ].
 
     1 to:dim do:[:i |
-         (d at:(i + 1)) at:1 put:(  ((d at:i) at:1) + deleteWeight )
+	 (d at:(i + 1)) at:1 put:(  ((d at:i) at:1) + deleteWeight )
     ].
 
     1 to:len1 do:[:i |
-        c1 := self at:i.
-        1 to:len2 do:[:j |
-            c2 := aString at:j.
-            (c1 == c2) ifTrue:[
-                pp := 0
-            ] ifFalse:[
-                (c1 asLowercase == c2 asLowercase) ifTrue:[
-                    pp := caseWeight
-                ] ifFalse:[
-                    pp := substWeight
-                ]
-            ].
-            prevRow := d at:i.
-            row := d at:(i + 1).
-            col := j + 1.
-            min := (prevRow at:j) + pp.
-            min := min min:( (row at:j) + insrtWeight).
-            min := min min:( (prevRow at:col) + deleteWeight).
-            row at:col put: min
-        ]
+	c1 := self at:i.
+	1 to:len2 do:[:j |
+	    c2 := aString at:j.
+	    (c1 == c2) ifTrue:[
+		pp := 0
+	    ] ifFalse:[
+		(c1 asLowercase == c2 asLowercase) ifTrue:[
+		    pp := caseWeight
+		] ifFalse:[
+		    pp := substWeight
+		]
+	    ].
+	    prevRow := d at:i.
+	    row := d at:(i + 1).
+	    col := j + 1.
+	    min := (prevRow at:j) + pp.
+	    min := min min:( (row at:j) + insrtWeight).
+	    min := min min:( (prevRow at:col) + deleteWeight).
+	    row at:col put: min
+	]
     ].
 
     ^ (d at:(len1 + 1)) at:(len2 + 1)
-
-    "'ocmprt' levenshteinTo:'computer'
-     'computer' levenshteinTo:'computer'
-     'ocmputer' levenshteinTo:'computer'
-     'cmputer' levenshteinTo:'computer'
-     'Computer' levenshteinTo:'computer'"
 !
 
 spellAgainst: aString 
     "return an integer between 0 and 100 indicating how similar 
-     the argument is to the receiver.  No case conversion is done."
+     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."
 
     | i1     "{ Class: SmallInteger }"
       i2     "{ Class: SmallInteger }"
+      next1  "{ Class: SmallInteger }"
+      next2  "{ Class: SmallInteger }"
       size1  "{ Class: SmallInteger }"
       size2  "{ Class: SmallInteger }"
       score  "{ Class: SmallInteger }"
@@ -959,36 +1048,40 @@
 
     size1 := self size.
     size2 := aString size.
-    maxLen := size1 max: size2.
+    maxLen := size1 max:size2.
     score := 0.
     i1 := i2 := 1.
     [i1 <= size1 and: [i2 <= size2]] whileTrue:[
-        (self at: i1) == (aString at: i2) ifTrue: [
-            score := score+1.             
-            i1 := i1+1.                    
-            i2 := i2+1
-        ] ifFalse: [
-            (i2 < size2 and: [(self at: i1) == (aString at: i2+1)]) ifTrue: [
-                i2 := i2+1
-            ] ifFalse: [
-                (i1 < size1 and: [(self at: i1+1) == (aString at: i2)]) ifTrue: [
-                    i1 := i1+1
-                ] ifFalse: [
-                    i1 := i1+1.
-                    i2 := i2+1
-                ] 
-            ] 
-        ] 
+	next1 := i1 + 1.
+	next2 := i2 + 1.
+	(self at:i1) == (aString at:i2) ifTrue: [
+	    score := score+1.             
+	    i1 := next1.                    
+	    i2 := next2
+	] ifFalse: [
+	    (i2 < size2 and: [(self at:i1) == (aString at:next2)]) ifTrue: [
+		i2 := next2
+	    ] ifFalse: [
+		(i1 < size1 and: [(self at:next1) == (aString at:i2)]) ifTrue: [
+		    i1 := next1
+		] ifFalse: [
+		    i1 := next1.
+		    i2 := next2
+		] 
+	    ] 
+	] 
     ].
 
-    score = maxLen ifTrue: [^100].
-    ^100*score//maxLen
+    score = maxLen ifTrue: [^ 100].
+    ^ 100 * score // maxLen
 
-    " 'Smalltalk' spellAgainst: 'Smalltlak' "
-    " 'Smalltalk' spellAgainst: 'smalltlak' "
-    " 'Smalltalk' spellAgainst: 'smalltalk' "
-    " 'Smalltalk' spellAgainst: 'smalltlk' "
-    " 'Smalltalk' spellAgainst: 'Smalltolk' "
+    " 
+     'Smalltalk' spellAgainst: 'Smalltlak' 
+     'Smalltalk' spellAgainst: 'smalltlak' 
+     'Smalltalk' spellAgainst: 'smalltalk' 
+     'Smalltalk' spellAgainst: 'smalltlk'  
+     'Smalltalk' spellAgainst: 'Smalltolk'   
+    "
 ! !
 
 !AbstractString methodsFor:'padded copying'!
@@ -1003,9 +1096,9 @@
 
     len := self size.
     len < newSize ifTrue:[
-        s := self species new:newSize withAll:padCharacter.
-        s replaceFrom:1 to:len with:self.
-        ^ s
+	s := self species new:newSize withAll:padCharacter.
+	s replaceFrom:1 to:len with:self.
+	^ s
     ]
 
     "
@@ -1028,9 +1121,9 @@
 
     len := self size.
     (len < size) ifTrue:[
-        s := self species new:size withAll:padCharacter.
-        s replaceFrom:(size - len + 1) with:self.
-        ^ s
+	s := self species new:size withAll:padCharacter.
+	s replaceFrom:(size - len + 1) with:self.
+	^ s
     ]
 
     "
@@ -1074,21 +1167,21 @@
     startIndex := 0.
     sz := self size.
     startIndex == 0 ifTrue:[
-        startIndex := 1.
-        endIndex := sz.
-        blank := Character space.
-        [(startIndex < endIndex) and:[(self at:startIndex) == blank]] whileTrue:[
-            startIndex := startIndex + 1
-        ].
-        [(endIndex > 1) and:[(self at:endIndex) == blank]] whileTrue:[
-            endIndex := endIndex - 1
-        ]
+	startIndex := 1.
+	endIndex := sz.
+	blank := Character space.
+	[(startIndex < endIndex) and:[(self at:startIndex) == blank]] whileTrue:[
+	    startIndex := startIndex + 1
+	].
+	[(endIndex > 1) and:[(self at:endIndex) == blank]] whileTrue:[
+	    endIndex := endIndex - 1
+	]
     ].
     startIndex > endIndex ifTrue:[
-        ^ ''
+	^ ''
     ].
     ((startIndex == 1) and:[endIndex == sz]) ifTrue:[
-        ^ self
+	^ self
     ].
     ^ self copyFrom:startIndex to:endIndex
 
@@ -1110,20 +1203,20 @@
     startIndex := 0.
     sz := self size.
     startIndex == 0 ifTrue:[
-        startIndex := 1.
-        endIndex := self size.
-        [(startIndex < endIndex) and:[(self at:startIndex) isSeparator]] whileTrue:[
-            startIndex := startIndex + 1
-        ].
-        [(endIndex > 1) and:[(self at:endIndex) isSeparator]] whileTrue:[
-            endIndex := endIndex - 1
-        ].
+	startIndex := 1.
+	endIndex := self size.
+	[(startIndex < endIndex) and:[(self at:startIndex) isSeparator]] whileTrue:[
+	    startIndex := startIndex + 1
+	].
+	[(endIndex > 1) and:[(self at:endIndex) isSeparator]] whileTrue:[
+	    endIndex := endIndex - 1
+	].
     ].
     startIndex > endIndex ifTrue:[
-        ^ ''
+	^ ''
     ].
     ((startIndex == 1) and:[endIndex == sz]) ifTrue:[
-        ^ self
+	^ self
     ].
     ^ self copyFrom:startIndex to:endIndex
 
@@ -1131,8 +1224,34 @@
      '    foo    ' withoutSeparators   
      ('  foo' , Character tab asString , '    ') withoutSeparators inspect 
     "
+!
+
+withTabs
+    "return a copy of the receiver where leading spaces are
+     replaced by tabulator characters (assuming 8-col tabs)"
+
+    |idx nTabs newString|
+
+    idx := self findFirst:[:c | (c ~~ Character space)].
+    nTabs := (idx-1) // 8.
+    nTabs == 0 ifTrue:[^ self].
+
+    "any tabs"
+    newString := self class new:(self size - (nTabs * 7)).
+    newString atAll:(1 to:nTabs) put:(Character tab).
+    newString replaceFrom:(nTabs + 1) with:self startingAt:(nTabs * 8 + 1).
+    ^ newString
+
+    "
+     '12345678901234567890' withTabs 
+     '       8901234567890' withTabs 
+     '        901234567890' withTabs  
+     '               67890' withTabs
+     '                7890' withTabs
+     '                 890' withTabs
+    "
 ! !
-
+        
 !AbstractString methodsFor:'queries'!
 
 isString