#DOCUMENTATION by cg
authorClaus Gittinger <cg@exept.de>
Sun, 10 Feb 2019 14:49:45 +0100
changeset 23701 8f66659ef900
parent 23700 962839a1b505
child 23702 6b11890f5f2c
#DOCUMENTATION by cg class: CharacterArray category of:17 methods
CharacterArray.st
--- a/CharacterArray.st	Sun Feb 10 14:49:30 2019 +0100
+++ b/CharacterArray.st	Sun Feb 10 14:49:45 2019 +0100
@@ -6273,6 +6273,39 @@
 
 !CharacterArray methodsFor:'queries'!
 
+argumentCount
+    "treating the receiver as a message selector, return how many arguments would it take (ANSI)"
+
+    |binopChars|
+
+    (self size <= Method maxBinarySelectorSize) ifTrue:[
+        binopChars := Method binarySelectorCharacters.
+        (self conform:[:eachChar | (binopChars includes:eachChar)]) ifTrue:[
+            ^ 1
+        ].
+    ].
+    ^ self occurrencesOf:$:
+
+    "
+     'foo:bar:' argumentCount
+     #foo:bar: argumentCount
+     'hello' argumentCount
+     '+' argumentCount
+     '++' argumentCount
+     '+++' argumentCount
+     '|' argumentCount
+     '?' argumentCount
+     '_' argumentCount
+     '_:' argumentCount
+     '_:_:' argumentCount
+     '<->' argumentCount
+     '<' argumentCount
+     #'<' argumentCount
+    "
+
+    "Modified (comment): / 06-02-2017 / 13:48:57 / cg"
+!
+
 bitsPerCharacter
     "return the underlying string's bitsPerCharacter
      (i.e. is it a regular String or a TwoByteString)"
@@ -6319,6 +6352,73 @@
     "
 !
 
+characterSize
+    "answer the size in bits of my largest character (actually only 7, 8, 16 or 32)"
+
+    |string max
+     sz "{ Class:SmallInteger}" |
+
+    (string := self string) ~~ self ifTrue:[
+        ^ string characterSize.
+    ].
+
+    sz := self size.
+    max := 7.
+    1 to:sz do:[:idx |
+        |thisSize|
+
+        thisSize := (self at:idx) characterSize.
+        thisSize > max ifTrue:[
+            max := thisSize.
+            max == 32 ifTrue:[
+                "shortcut: we know, that max size is 32"
+                ^ 32.
+            ].
+        ].
+    ].
+
+    ^ max.
+
+    "
+     'hello' characterSize
+     'hello' asUnicode32String characterSize
+     'helloü' asUnicode32String characterSize
+     'hello' asText allBold characterSize
+    "
+!
+
+contains8BitCharacters
+    <resource: #obsolete>
+
+    ^ self containsNon7BitAscii
+!
+
+containsNon7BitAscii
+    "return true, if the underlying string contains 8BitCharacters (or widers)
+     (i.e. if it is non-ascii)"
+
+    |string
+     sz "{ Class:SmallInteger }"|
+
+    (string := self string) ~~ self ifTrue:[
+        ^ string containsNon7BitAscii
+    ].
+    sz := self size.
+    1 to:sz do:[:idx|
+        (self at:idx) codePoint > 16r7F ifTrue:[
+            ^ true.
+        ].
+    ].
+    ^ false.
+
+    "
+     'hello' asUnicode32String containsNon7BitAscii
+     'hello üöä' asUnicode32String containsNon7BitAscii
+     'hello' asUnicode32String asText allBold containsNon7BitAscii
+     'hello üö' asUnicode32String asText allBold containsNon7BitAscii
+    "
+!
+
 containsNon8BitElements
     "return true, if the underlying string contains elements larger than a single byte"
 
@@ -6449,6 +6549,155 @@
     "Modified: 12.5.1996 / 20:32:05 / cg"
 !
 
+isAlphaNumeric
+    "return true, if the receiver is some alphanumeric word;
+     i.e. consists of a letter followed by letters or digits."
+
+    self isEmpty ifTrue:[
+        "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
+    "
+
+    "Modified: / 13-10-2006 / 12:53:49 / cg"
+!
+
+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"
+
+    |binopChars|
+
+    (self size > Method maxBinarySelectorSize) ifTrue:[^ false].
+
+    binopChars := Method binarySelectorCharacters.
+    ^ (self conform:[:char | (binopChars includes:char)])
+
+    "
+     'foo:bar:' isBinarySelector
+     #foo:bar: isBinarySelector
+     'hello' isBinarySelector
+     '+' isBinarySelector
+     '|' isBinarySelector
+     '?' isBinarySelector
+     ':' isBinarySelector
+     'a:' isBinarySelector
+     '->' isBinarySelector
+     '<->' isBinarySelector
+     '::' isBinarySelector
+    "
+
+    "Modified: / 04-01-1997 / 14:16:14 / cg"
+    "Modified (comment): / 13-02-2017 / 19:57:29 / cg"
+!
+
+isBlank
+    "return true, if the receiver contains spaces only"
+
+    ^ self size == 0 or:[(self contains:[:char | char ~~ Character space]) not]
+
+    "
+     '' isBlank
+     '' asUnicode16String isBlank
+     '   a    ' isBlank
+     '        ' isBlank
+     '        ' asUnicode16String isBlank
+    "
+
+    "Modified (comment): / 14-09-2018 / 10:04:18 / Stefan Vogel"
+!
+
+isInfix
+    "return true, if the receiver is a binary message selector"
+
+    ^ self first isLetterOrDigit not
+
+    "
+     #at:put: isInfix
+     #at: isInfix
+     #+ isInfix
+     #size isInfix
+    "
+
+    "Created: / 1.11.1997 / 12:34:55 / cg"
+    "Modified: / 1.11.1997 / 12:36:37 / cg"
+!
+
+isKeyword
+    "return true, if the receiver is a keyword message selector.
+     This is a quick check, which only looks at the last character.
+     Should only be used, if we already know that the receiver forms a valid selector.
+     To check an arbitrary string, use isKeywordSelector.
+     Bad naming, but compatibility is asking for it."
+
+    ^ self last == $:
+
+    "
+     #at:put: isKeyword
+     #at: isKeyword
+     #+ isKeyword
+     #size isKeyword
+    "
+
+    "Created: / 01-11-1997 / 12:34:55 / cg"
+    "Modified (comment): / 30-04-2016 / 18:19:11 / cg"
+!
+
+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."
+
+    |state|
+
+    (self size == 0) ifTrue:[^ false].
+    (self last == $:) ifFalse:[^ false].
+
+    state := #initial.
+    self do:[:char |
+        (state == #initial or:[ state == #gotColon]) ifTrue:[
+            (char isLetterOrUnderline) ifFalse:[^ false].
+            state := #gotCharacter.
+        ] ifFalse:[
+            char == $: ifTrue:[
+                state := #gotColon.
+            ] ifFalse:[
+                (char isLetterOrDigit or:[char == $_]) ifFalse:[^ false].
+            ].
+        ].
+    ].
+    ^ state == #gotColon.
+
+    "
+     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).
+    "
+
+    "Modified (comment): / 30-04-2016 / 18:20:14 / cg"
+!
+
 isLowercaseFirst
     "return true, if the first character is a lowercase character."
 
@@ -6460,6 +6709,58 @@
     "
 !
 
+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."
+
+    |i|
+
+    (self at:1) == $: ifFalse:[^ false].
+
+    i := self indexOf:$: startingAt:2.
+    i == 0 ifTrue:[^ false].
+    self size <= (i+1) ifTrue:[^ false].
+    (self at:i+1) == $: ifFalse:[^ false].
+    (self at:i+2) == $: ifTrue:[^ false].
+    "/ could check if the rest after the ns-prefix and colons is a valid selector...
+    ^ true
+
+    "test:
+     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"
+!
+
+isNumeric
+    "return true, if the receiver is some numeric word;
+     i.e. consists only of digits."
+
+    self size == 0 ifTrue:[
+        ^ false
+    ].
+    ^ self conform:[:char | char isDigit]
+
+    "
+     'helloWorld' isNumeric
+     'foo1234' isNumeric
+     'f1234' isNumeric
+     '1234' isNumeric
+     '+' isNumeric
+    "
+
+    "Modified: / 13-10-2006 / 12:54:12 / cg"
+!
+
 isUppercaseFirst
     "return true, if the first character is an uppercase character."
 
@@ -6471,6 +6772,51 @@
     "
 !
 
+isValidSmalltalkIdentifier
+    "return true, if the receiver's characters make up a valid smalltalk identifier"
+
+    |scanner tok|
+
+    scanner := Compiler new.
+    scanner source:(self readStream).
+    ParseError handle:[:ex |
+        tok := nil.
+    ] do:[
+        tok := scanner nextToken.
+    ].
+    tok ~~ #Identifier ifTrue:[
+        ^ false
+    ].
+    scanner tokenPosition == 1 ifFalse:[^ false].
+    ^ scanner sourceStream atEnd.
+
+    "
+     'foo' isValidSmalltalkIdentifier
+     '1foo' isValidSmalltalkIdentifier
+     '_foo' isValidSmalltalkIdentifier
+     '_foo_bar_' isValidSmalltalkIdentifier
+     'foo ' isValidSmalltalkIdentifier
+     ' foo' isValidSmalltalkIdentifier
+    "
+!
+
+isWhitespace
+    "return true, if the receiver is empty or contains only whitespace."
+
+    ^ (self indexOfNonSeparatorStartingAt:1) == 0
+
+    "
+     '' isWhitespace
+     '   ' isWhitespace
+     '   \    \' withCRs isWhitespace
+     '   a\    \' withCRs isWhitespace
+     '   \    \a' withCRs isWhitespace
+     'a   \    \a' withCRs isWhitespace
+    "
+
+    "Created: / 01-03-2017 / 15:24:53 / cg"
+!
+
 keywords
     "assuming the receiver is a keyword message selector,
      return the individual keywords (i.e. break it up at colons)
@@ -6563,6 +6909,47 @@
     "Modified: / 06-03-2007 / 11:51:15 / cg"
 !
 
+numArgs
+    <resource: #obsolete>
+    "treating the receiver as a message selector, return how many arguments would it take.
+     Please use argumentCount for ANSI compatibility."
+
+    ^ self argumentCount
+!
+
+partsIfSelector
+    "treat the receiver as a message selector, return a collection of parts.
+     Notice: this is more tolerant than Smalltalk's syntax would suggest;
+     especially it allows for empty keyword parts between colons.
+     This is not (and should not be checked here), to allow parsing of
+     degenerate selectors as appearing with objectiveC."
+
+    |idx1 "{ Class: SmallInteger }"
+     coll idx2 sz|
+
+    coll := OrderedCollection new.
+    idx1 := 1.
+    sz := self size.
+    [
+        idx2 := self indexOf:$: startingAt:idx1.
+        (idx2 == 0 or:[idx2 == sz]) ifTrue:[
+            coll add:(self copyFrom:idx1).
+            ^ coll
+        ].
+        coll add:(self copyFrom:idx1 to:idx2).
+        idx1 := idx2 + 1
+    ] loop.
+
+    "
+     'foo:' partsIfSelector
+     'foo:bar:' partsIfSelector
+     'foo::::' partsIfSelector
+     #foo:bar: partsIfSelector
+     'hello' partsIfSelector
+     '+' partsIfSelector
+    "
+!
+
 speciesForSubcollection
     "answer the class, when splitting instances into subcollections"
 
@@ -8430,307 +8817,6 @@
 
 !CharacterArray methodsFor:'testing'!
 
-argumentCount
-    "treating the receiver as a message selector, return how many arguments would it take (ANSI)"
-
-    |binopChars|
-
-    (self size <= Method maxBinarySelectorSize) ifTrue:[
-        binopChars := Method binarySelectorCharacters.
-        (self conform:[:eachChar | (binopChars includes:eachChar)]) ifTrue:[
-            ^ 1
-        ].
-    ].
-    ^ self occurrencesOf:$:
-
-    "
-     'foo:bar:' argumentCount
-     #foo:bar: argumentCount
-     'hello' argumentCount
-     '+' argumentCount
-     '++' argumentCount
-     '+++' argumentCount
-     '|' argumentCount
-     '?' argumentCount
-     '_' argumentCount
-     '_:' argumentCount
-     '_:_:' argumentCount
-     '<->' argumentCount
-     '<' argumentCount
-     #'<' argumentCount
-    "
-
-    "Modified (comment): / 06-02-2017 / 13:48:57 / cg"
-!
-
-characterSize
-    "answer the size in bits of my largest character (actually only 7, 8, 16 or 32)"
-
-    |string max
-     sz "{ Class:SmallInteger}" |
-
-    (string := self string) ~~ self ifTrue:[
-        ^ string characterSize.
-    ].
-
-    sz := self size.
-    max := 7.
-    1 to:sz do:[:idx |
-        |thisSize|
-
-        thisSize := (self at:idx) characterSize.
-        thisSize > max ifTrue:[
-            max := thisSize.
-            max == 32 ifTrue:[
-                "shortcut: we know, that max size is 32"
-                ^ 32.
-            ].
-        ].
-    ].
-
-    ^ max.
-
-    "
-     'hello' characterSize
-     'hello' asUnicode32String characterSize
-     'helloü' asUnicode32String characterSize
-     'hello' asText allBold characterSize
-    "
-!
-
-contains8BitCharacters
-    <resource: #obsolete>
-
-    ^ self containsNon7BitAscii
-!
-
-containsNon7BitAscii
-    "return true, if the underlying string contains 8BitCharacters (or widers)
-     (i.e. if it is non-ascii)"
-
-    |string
-     sz "{ Class:SmallInteger }"|
-
-    (string := self string) ~~ self ifTrue:[
-        ^ string containsNon7BitAscii
-    ].
-    sz := self size.
-    1 to:sz do:[:idx|
-        (self at:idx) codePoint > 16r7F ifTrue:[
-            ^ true.
-        ].
-    ].
-    ^ false.
-
-    "
-     'hello' asUnicode32String containsNon7BitAscii
-     'hello üöä' asUnicode32String containsNon7BitAscii
-     'hello' asUnicode32String asText allBold containsNon7BitAscii
-     'hello üö' asUnicode32String asText allBold containsNon7BitAscii
-    "
-!
-
-isAlphaNumeric
-    "return true, if the receiver is some alphanumeric word;
-     i.e. consists of a letter followed by letters or digits."
-
-    self isEmpty ifTrue:[
-        "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
-    "
-
-    "Modified: / 13-10-2006 / 12:53:49 / cg"
-!
-
-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"
-
-    |binopChars|
-
-    (self size > Method maxBinarySelectorSize) ifTrue:[^ false].
-
-    binopChars := Method binarySelectorCharacters.
-    ^ (self conform:[:char | (binopChars includes:char)])
-
-    "
-     'foo:bar:' isBinarySelector
-     #foo:bar: isBinarySelector
-     'hello' isBinarySelector
-     '+' isBinarySelector
-     '|' isBinarySelector
-     '?' isBinarySelector
-     ':' isBinarySelector
-     'a:' isBinarySelector
-     '->' isBinarySelector
-     '<->' isBinarySelector
-     '::' isBinarySelector
-    "
-
-    "Modified: / 04-01-1997 / 14:16:14 / cg"
-    "Modified (comment): / 13-02-2017 / 19:57:29 / cg"
-!
-
-isBlank
-    "return true, if the receiver contains spaces only"
-
-    ^ self size == 0 or:[(self contains:[:char | char ~~ Character space]) not]
-
-    "
-     '' isBlank
-     '' asUnicode16String isBlank
-     '   a    ' isBlank
-     '        ' isBlank
-     '        ' asUnicode16String isBlank
-    "
-
-    "Modified (comment): / 14-09-2018 / 10:04:18 / Stefan Vogel"
-!
-
-isInfix
-    "return true, if the receiver is a binary message selector"
-
-    ^ self first isLetterOrDigit not
-
-    "
-     #at:put: isInfix
-     #at: isInfix
-     #+ isInfix
-     #size isInfix
-    "
-
-    "Created: / 1.11.1997 / 12:34:55 / cg"
-    "Modified: / 1.11.1997 / 12:36:37 / cg"
-!
-
-isKeyword
-    "return true, if the receiver is a keyword message selector.
-     This is a quick check, which only looks at the last character.
-     Should only be used, if we already know that the receiver forms a valid selector.
-     To check an arbitrary string, use isKeywordSelector.
-     Bad naming, but compatibility is asking for it."
-
-    ^ self last == $:
-
-    "
-     #at:put: isKeyword
-     #at: isKeyword
-     #+ isKeyword
-     #size isKeyword
-    "
-
-    "Created: / 01-11-1997 / 12:34:55 / cg"
-    "Modified (comment): / 30-04-2016 / 18:19:11 / cg"
-!
-
-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."
-
-    |state|
-
-    (self size == 0) ifTrue:[^ false].
-    (self last == $:) ifFalse:[^ false].
-
-    state := #initial.
-    self do:[:char |
-        (state == #initial or:[ state == #gotColon]) ifTrue:[
-            (char isLetterOrUnderline) ifFalse:[^ false].
-            state := #gotCharacter.
-        ] ifFalse:[
-            char == $: ifTrue:[
-                state := #gotColon.
-            ] ifFalse:[
-                (char isLetterOrDigit or:[char == $_]) ifFalse:[^ false].
-            ].
-        ].
-    ].
-    ^ state == #gotColon.
-
-    "
-     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).
-    "
-
-    "Modified (comment): / 30-04-2016 / 18:20:14 / cg"
-!
-
-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."
-
-    |i|
-
-    (self at:1) == $: ifFalse:[^ false].
-
-    i := self indexOf:$: startingAt:2.
-    i == 0 ifTrue:[^ false].
-    self size <= (i+1) ifTrue:[^ false].
-    (self at:i+1) == $: ifFalse:[^ false].
-    (self at:i+2) == $: ifTrue:[^ false].
-    "/ could check if the rest after the ns-prefix and colons is a valid selector...
-    ^ true
-
-    "test:
-     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"
-!
-
-isNumeric
-    "return true, if the receiver is some numeric word;
-     i.e. consists only of digits."
-
-    self size == 0 ifTrue:[
-        ^ false
-    ].
-    ^ self conform:[:char | char isDigit]
-
-    "
-     'helloWorld' isNumeric
-     'foo1234' isNumeric
-     'f1234' isNumeric
-     '1234' isNumeric
-     '+' isNumeric
-    "
-
-    "Modified: / 13-10-2006 / 12:54:12 / cg"
-!
-
 isPlainString
     "return true, if the receiver is a plain string (without attributes);
      true is returned here - redefinition of Object>>isPlainString."
@@ -8781,51 +8867,6 @@
     ^ false
 !
 
-isValidSmalltalkIdentifier
-    "return true, if the receiver's characters make up a valid smalltalk identifier"
-
-    |scanner tok|
-
-    scanner := Compiler new.
-    scanner source:(self readStream).
-    ParseError handle:[:ex |
-        tok := nil.
-    ] do:[
-        tok := scanner nextToken.
-    ].
-    tok ~~ #Identifier ifTrue:[
-        ^ false
-    ].
-    scanner tokenPosition == 1 ifFalse:[^ false].
-    ^ scanner sourceStream atEnd.
-
-    "
-     'foo' isValidSmalltalkIdentifier
-     '1foo' isValidSmalltalkIdentifier
-     '_foo' isValidSmalltalkIdentifier
-     '_foo_bar_' isValidSmalltalkIdentifier
-     'foo ' isValidSmalltalkIdentifier
-     ' foo' isValidSmalltalkIdentifier
-    "
-!
-
-isWhitespace
-    "return true, if the receiver is empty or contains only whitespace."
-
-    ^ (self indexOfNonSeparatorStartingAt:1) == 0
-
-    "
-     '' isWhitespace
-     '   ' isWhitespace
-     '   \    \' withCRs isWhitespace
-     '   a\    \' withCRs isWhitespace
-     '   \    \a' withCRs isWhitespace
-     'a   \    \a' withCRs isWhitespace
-    "
-
-    "Created: / 01-03-2017 / 15:24:53 / cg"
-!
-
 isWideString
     "true if I require more than one byte per character"
 
@@ -8835,47 +8876,6 @@
         ^ string isWideString.
     ].
     ^ self contains:[:aCharacter | aCharacter codePoint > 16rFF].
-!
-
-numArgs
-    <resource: #obsolete>
-    "treating the receiver as a message selector, return how many arguments would it take.
-     Please use argumentCount for ANSI compatibility."
-
-    ^ self argumentCount
-!
-
-partsIfSelector
-    "treat the receiver as a message selector, return a collection of parts.
-     Notice: this is more tolerant than Smalltalk's syntax would suggest;
-     especially it allows for empty keyword parts between colons.
-     This is not (and should not be checked here), to allow parsing of
-     degenerate selectors as appearing with objectiveC."
-
-    |idx1 "{ Class: SmallInteger }"
-     coll idx2 sz|
-
-    coll := OrderedCollection new.
-    idx1 := 1.
-    sz := self size.
-    [
-        idx2 := self indexOf:$: startingAt:idx1.
-        (idx2 == 0 or:[idx2 == sz]) ifTrue:[
-            coll add:(self copyFrom:idx1).
-            ^ coll
-        ].
-        coll add:(self copyFrom:idx1 to:idx2).
-        idx1 := idx2 + 1
-    ] loop.
-
-    "
-     'foo:' partsIfSelector
-     'foo:bar:' partsIfSelector
-     'foo::::' partsIfSelector
-     #foo:bar: partsIfSelector
-     'hello' partsIfSelector
-     '+' partsIfSelector
-    "
 ! !
 
 !CharacterArray methodsFor:'tracing'!