1"======================================================================
2|
3|   String Method Definitions
4|
5|
6 ======================================================================"
7
8"======================================================================
9|
10| Copyright 1988,92,94,95,99,2000,2001,2006,2008,2009
11| Free Software Foundation, Inc.
12| Written by Steve Byrne.
13|
14| This file is part of the GNU Smalltalk class library.
15|
16| The GNU Smalltalk class library is free software; you can redistribute it
17| and/or modify it under the terms of the GNU Lesser General Public License
18| as published by the Free Software Foundation; either version 2.1, or (at
19| your option) any later version.
20|
21| The GNU Smalltalk class library is distributed in the hope that it will be
22| useful, but WITHOUT ANY WARRANTY; without even the implied warranty of
23| MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
24| General Public License for more details.
25|
26| You should have received a copy of the GNU Lesser General Public License
27| along with the GNU Smalltalk class library; see the file COPYING.LIB.
28| If not, write to the Free Software Foundation, 59 Temple Place - Suite
29| 330, Boston, MA 02110-1301, USA.
30|
31 ======================================================================"
32
33
34
35CharacterArray subclass: String [
36
37    <shape: #character>
38    <category: 'Collections-Text'>
39    <comment: 'My instances represent 8-bit character strings.  Being a very common
40case, they are particularly optimized.
41
42Note that, if you care about multilingualization, you should treat
43String only as an encoded representation of a UnicodeString.  The I18N
44package adds more Unicode-friendliness to the system so that encoding
45and decoding is performed automatically in more cases.  In that case,
46String represents a case when the encoding is either unknown, irrelevant,
47or assumed to be the system default.'>
48
49    String class >> fromCData: aCObject [
50	"Answer a String containing the bytes starting at the location pointed
51	 to by aCObject, up to the first NUL character."
52
53	<category: 'instance creation'>
54	<primitive: VMpr_String_fromCData>
55	^self primitiveFailed
56    ]
57
58    String class >> fromCData: aCObject size: anInteger [
59	"Answer a String containing anInteger bytes starting at the location pointed
60	 to by aCObject"
61
62	<category: 'instance creation'>
63	<primitive: VMpr_String_fromCData_size>
64	^SystemExceptions.WrongClass signalOn: anInteger mustBe: SmallInteger
65    ]
66
67    String class >> isUnicode [
68	"Answer false; the receiver stores bytes (i.e. an encoded
69	 form), not characters."
70
71	<category: 'multibyte encodings'>
72	^false
73    ]
74
75    = aCollection [
76	"Answer whether the receiver's items match those in aCollection"
77
78	<category: 'basic'>
79	<primitive: VMpr_ArrayedCollection_equal>
80	^super = aCollection
81    ]
82
83    , aString [
84	"Answer a new instance of an ArrayedCollection containing all the elements
85	 in the receiver, followed by all the elements in aSequenceableCollection"
86
87	<category: 'basic'>
88	| newString mySize |
89	aString class == String ifFalse: [^super , aString].
90	newString := self copyEmpty: (mySize := self size) + aString size.
91	newString
92	    replaceFrom: 1
93	    to: mySize
94	    with: self
95	    startingAt: 1.
96	newString
97	    replaceFrom: mySize + 1
98	    to: newString size
99	    with: aString
100	    startingAt: 1.
101	^newString
102    ]
103
104    encoding [
105	"Answer the encoding of the receiver.  This is not implemented unless
106	 you load the Iconv package."
107
108	<category: 'converting'>
109	self notYetImplemented
110    ]
111
112    asByteArray [
113	"Return the receiver, converted to a ByteArray of ASCII values"
114
115	<category: 'converting'>
116	| byteArray size |
117	size := self size.
118	byteArray := ByteArray new: size.
119	byteArray
120	    replaceFrom: 1
121	    to: size
122	    withString: self
123	    startingAt: 1.
124	^byteArray
125    ]
126
127    asSymbol [
128	"Returns the symbol corresponding to the receiver"
129
130	<category: 'converting'>
131	^Symbol intern: self
132    ]
133
134    asString [
135	"But I already am a String!  Really!"
136
137	<category: 'converting'>
138	^self
139    ]
140
141    isString [
142	<category: 'testing functionality'>
143	^true
144    ]
145
146    displayString [
147	"Answer a String representing the receiver. For most objects
148	 this is simply its #printString, but for CharacterArrays and characters,
149	 superfluous dollars or extra pair of quotes are stripped."
150
151	<category: 'printing'>
152	^self
153    ]
154
155    displayOn: aStream [
156	"Print a representation of the receiver on aStream. Unlike
157	 #printOn:, this method strips extra quotes."
158
159	<category: 'printing'>
160	aStream nextPutAll: self
161    ]
162
163    isLiteralObject [
164	"Answer whether the receiver is expressible as a Smalltalk literal."
165
166	<category: 'printing'>
167	^self isReadOnly not
168    ]
169
170    storeLiteralOn: aStream [
171	"Store a Smalltalk literal compiling to the receiver on aStream"
172
173	<category: 'printing'>
174	aStream nextPut: $'.
175	self do:
176		[:char |
177		char == $' ifTrue: [aStream nextPut: char].
178		aStream nextPut: char].
179	aStream nextPut: $'
180    ]
181
182    storeOn: aStream [
183	"Store Smalltalk code compiling to the receiver on aStream"
184
185	<category: 'printing'>
186	self storeLiteralOn: aStream.
187	self isReadOnly ifFalse: [aStream nextPutAll: ' copy']
188    ]
189
190    printOn: aStream [
191	"Print a representation of the receiver on aStream"
192
193	<category: 'printing'>
194	aStream nextPut: $'.
195	self do:
196		[:char |
197		char == $' ifTrue: [aStream nextPut: char].
198		aStream nextPut: char].
199	aStream nextPut: $'
200    ]
201
202    byteAt: index [
203	"Answer the ascii value of index-th character variable of the receiver"
204
205	<category: 'accessing'>
206	^self valueAt: index
207    ]
208
209    byteAt: index put: value [
210	"Store (Character value: value) in the index-th indexed instance variable
211	 of the receiver"
212
213	<category: 'accessing'>
214	^self valueAt: index put: value
215    ]
216
217    hash [
218	"Answer an hash value for the receiver"
219
220	<category: 'built ins'>
221	<primitive: VMpr_String_hash>
222	^0
223    ]
224
225    similarityTo: aString [
226	"Answer a number that denotes the similarity between aString and
227	 the receiver.  0 indicates equality, negative numbers indicate
228	 some difference.  Implemented as a primitive for speed."
229
230	<category: 'built ins'>
231	<primitive: VMpr_String_similarityTo>
232	^SystemExceptions.WrongClass signalOn: aString mustBe: String
233    ]
234
235    size [
236	"Answer the size of the receiver"
237
238	<category: 'built ins'>
239	<primitive: VMpr_Object_basicSize>
240	^self primitiveFailed
241    ]
242
243    indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock [
244	"Answer the first index > anIndex which contains anElement.
245	 Invoke exceptionBlock and answer its result if no item is found"
246
247	<category: 'basic'>
248	<primitive: VMpr_ArrayedCollection_indexOfStartingAt>
249	"If anIndex is just past the end of the collection, don't raise
250	 an error (this is the most generic solution that avoids that
251	 #indexOf: fails when the collection is empty."
252	^(anIndex < 1 or: [anIndex > (self size + 1)])
253	    ifTrue: [self checkIndexableBounds: anIndex]
254	    ifFalse: [exceptionBlock value]
255    ]
256
257    indexOf: anElement startingAt: anIndex [
258	"Answer the first index > anIndex which contains anElement.
259	 Invoke exceptionBlock and answer its result if no item is found"
260
261	<category: 'basic'>
262	<primitive: VMpr_ArrayedCollection_indexOfStartingAt>
263	"If anIndex is just past the end of the collection, don't raise
264	 an error (this is the most generic solution that avoids that
265	 #indexOf: fails when the collection is empty."
266	^(anIndex < 1 or: [anIndex > (self size + 1)])
267	    ifTrue: [self checkIndexableBounds: anIndex]
268	    ifFalse: [0]
269    ]
270
271    replaceFrom: start to: stop withByteArray: byteArray startingAt: replaceStart [
272	"Replace the characters from start to stop with new characters whose
273	 ASCII codes are contained in byteArray, starting at the replaceStart
274	 location of byteArray"
275
276	<category: 'built ins'>
277	<primitive: VMpr_ArrayedCollection_replaceFromToWithStartingAt>
278	^super
279	    replaceFrom: start
280	    to: stop
281	    with: byteArray asString
282	    startingAt: replaceStart
283    ]
284
285    replaceFrom: start to: stop with: aString startingAt: replaceStart [
286	"Replace the characters from start to stop with new characters whose
287	 ASCII codes are contained in aString, starting at the replaceStart
288	 location of aString"
289
290	<category: 'built ins'>
291	<primitive: VMpr_ArrayedCollection_replaceFromToWithStartingAt>
292	^super
293	    replaceFrom: start
294	    to: stop
295	    with: aString
296	    startingAt: replaceStart
297    ]
298
299    at: anIndex ifAbsent: aBlock [
300	"Answer the index-th indexed instance variable of the receiver"
301
302	<category: 'built ins'>
303	<primitive: VMpr_Object_basicAt>
304	^self checkIndexableBounds: anIndex ifAbsent: aBlock
305    ]
306
307    at: anIndex [
308	"Answer the index-th indexed instance variable of the receiver"
309
310	<category: 'built ins'>
311	<primitive: VMpr_Object_basicAt>
312	self checkIndexableBounds: anIndex
313    ]
314
315    basicAt: anIndex [
316	"Answer the index-th indexed instance variable of the receiver.
317	 This method must not be overridden, override at: instead"
318
319	<category: 'built ins'>
320	<primitive: VMpr_Object_basicAt>
321	self checkIndexableBounds: anIndex
322    ]
323
324    at: anIndex put: value [
325	"Store value in the index-th indexed instance variable of the receiver"
326
327	<category: 'built ins'>
328	<primitive: VMpr_Object_basicAtPut>
329	self checkIndexableBounds: anIndex put: value
330    ]
331
332    basicAt: anIndex put: value [
333	"Store value in the index-th indexed instance variable of the receiver
334	 This method must not be overridden, override at:put: instead"
335
336	<category: 'built ins'>
337	<primitive: VMpr_Object_basicAtPut>
338	self checkIndexableBounds: anIndex put: value
339    ]
340
341    asCData [
342	"Allocate memory with malloc for a NULL-terminated copy of the
343         receiver, and return a pointer to it as a CChar."
344
345	<category: 'CObject'>
346	^self asCData: CCharType
347    ]
348
349    asCData: aCType [
350	"Allocate memory with malloc for a NULL-terminated copy of the
351        receiver, and return a pointer to it as a CObject of the given type."
352
353	<category: 'built ins'>
354	<primitive: VMpr_String_asCData>
355	^self primitiveFailed
356    ]
357]
358
359