|
|
6.26 CharacterArray
- Defined in namespace Smalltalk
- Category: Language-Data types
- My instances represent a generic textual (string) data type. I provide
accessing and manipulation methods for strings.
6.26.1 CharacterArray class: basic
- fromString: aCharacterArray
- Make up an instance of the receiver containing the same characters as aCharacterArray, and answer it.
- lineDelimiter
- Answer a CharacterArray which one can use as a line delimiter.
6.26.2 CharacterArray: basic
- basicAt: index
- Answer the index-th character of the receiver. This is an exception to the `do not override' rule that allows storage optimization by storing the characters as values instead of as objects.
- basicAt: index put: anObject
- Set the index-th character of the receiver to be anObject. This method must not be overridden; override at: instead. String overrides it so that it looks like it contains character objects even though it contains bytes
6.26.3 CharacterArray: built ins
- valueAt: index
- Answer the ascii value of index-th character variable of the receiver
- valueAt: index put: value
- Store (Character value: value) in the index-th indexed instance variable of the receiver
6.26.4 CharacterArray: comparing
- < aCharacterArray
- Return true if the receiver is less than aCharacterArray, ignoring case differences.
- <= aCharacterArray
- Returns true if the receiver is less than or equal to aCharacterArray, ignoring case differences. If is receiver is an initial substring of aCharacterArray, it is considered to be less than aCharacterArray.
- > aCharacterArray
- Return true if the receiver is greater than aCharacterArray, ignoring case differences.
- >= aCharacterArray
- Returns true if the receiver is greater than or equal to aCharacterArray, ignoring case differences. If is aCharacterArray is an initial substring of the receiver, it is considered to be less than the receiver.
- indexOf: aCharacterArray matchCase: aBoolean startingAt: anIndex
- Answer an Interval of indices in the receiver which match the aCharacterArray pattern. # in aCharacterArray means 'match any character', * in aCharacterArray means 'match any sequence of characters'. The first item of the returned in- terval is >= anIndex. If aBoolean is false, the search is case-insen- sitive, else it is case-sensitive. If no Interval matches the pattern, answer nil.
- match: aCharacterArray
- Answer whether aCharacterArray matches the pattern contained in the receiver. # in the receiver means 'match any character', * in receiver means 'match any sequence of characters'.
- sameAs: aCharacterArray
- Returns true if the receiver is the same CharacterArray as aCharacterArray, ignoring case differences.
- startsWith: aCharacterArray
- Returns true if the receiver starts with the same characters as aCharacterArray.
6.26.5 CharacterArray: converting
- asByteArray
- Return the receiver, converted to a ByteArray of ASCII values
- asClassPoolKey
- Return the receiver, ready to be put in a class pool dictionary
- asGlobalKey
- Return the receiver, ready to be put in the Smalltalk dictionary
- asInteger
- Parse an Integer number from the receiver until the input character is invalid and answer the result at this point
- asLowercase
- Returns a copy of self as a lowercase CharacterArray
- asNumber
- Parse a Number from the receiver until the input character is invalid and answer the result at this point
- asPoolKey
- Return the receiver, ready to be put in a pool dictionary
- asString
- But I already am a String! Really!
- asSymbol
- Returns the symbol corresponding to the CharacterArray
- asUppercase
- Returns a copy of self as an uppercase CharacterArray
- fileName
- But I don't HAVE a file name!
- filePos
- But I don't HAVE a file position!
- isNumeric
- Answer whether the receiver denotes a number
- trimSeparators
- Return a copy of the reciever without any spaces on front or back. The implementation is protected against the `all blanks' case.
6.26.6 CharacterArray: copying
- deepCopy
- Returns a deep copy of the receiver. This is the same thing as a shallow copy for CharacterArrays
- shallowCopy
- Returns a shallow copy of the receiver
6.26.7 CharacterArray: printing
- displayOn: aStream
- Print a representation of the receiver on aStream. Unlike #printOn:, this method strips extra quotes.
- displayString
- Answer a String representing the receiver. For most objects this is simply its #printString, but for CharacterArrays and characters, superfluous dollars or extra pair of quotes are stripped.
- printOn: aStream
- Print a representation of the receiver on aStream
6.26.8 CharacterArray: storing
- storeOn: aStream
- Print Smalltalk code compiling to the receiver on aStream
6.26.9 CharacterArray: string processing
- bindWith: s1
- Answer the receiver with every %1 replaced by the displayString of s1
- bindWith: s1 with: s2
- Answer the receiver with every %1 or %2 replaced by s1 or s2, respectively. s1 and s2 are `displayed' (i.e. their displayString is used) upon replacement.
- bindWith: s1 with: s2 with: s3
- Answer the receiver with every %1, %2 or %3 replaced by s1, s2 or s3, respectively. s1, s2 and s3 are `displayed' (i.e. their displayString is used) upon replacement.
- bindWith: s1 with: s2 with: s3 with: s4
- Answer the receiver with every %1, %2, %3 or %4 replaced by s1, s2, s3 or s4, respectively. s1, s2, s3 and s4 are `displayed' (i.e. their displayString is used) upon replacement.
- bindWithArguments: anArray
- Answer the receiver with every %n (1<=n<=9) replaced by the n-th element of anArray. The replaced elements are `displayed' (i.e. their displayString is used)
- contractTo: smallSize
- Either return myself, or a copy shortened to smallSize characters by inserting an ellipsis (three dots: ...)
- substrings
- Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of white space characters
- substrings: aCharacter
- Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of characters matching aCharacter. This message is preserved for backwards compatibility; the ANSI standard mandates `subStrings:', with an uppercase s.
- subStrings: aCharacter
- Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of characters matching aCharacter
6.26.10 CharacterArray: testing functionality
- isCharacterArray
- Answer `true'.
|