1"======================================================================
2|
3|   SequenceableCollection Method Definitions
4|
5|
6 ======================================================================"
7
8"======================================================================
9|
10| Copyright 1988,92,94,95,99,2000,2001,2002,2003,2006,2007,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
35Collection subclass: SequenceableCollection [
36
37    <category: 'Collections-Sequenceable'>
38    <comment: 'My instances represent collections of objects that are ordered.  I provide
39some access and manipulation methods.'>
40
41    SequenceableCollection class >> join: aCollection separatedBy: sepCollection [
42	"Where aCollection is a collection of SequenceableCollections,
43	 answer a new instance with all the elements therein, in order,
44	 each separated by an occurrence of sepCollection."
45
46	<category: 'instance creation'>
47	| newInst start |
48	aCollection isEmpty ifTrue: [^self new: 0].
49	newInst := self
50		    new: (aCollection inject: sepCollection size * (aCollection size - 1)
51			    into: [:size :each | size + each size]).
52	aCollection do: [:subColl | newInst addAll: subColl]
53	    separatedBy: [newInst addAll: sepCollection].
54	^newInst
55    ]
56
57    examineOn: aStream [
58	"Print all the instance variables and context of the receiver on aStream"
59
60	<category: 'testing'>
61	| instVars object output |
62	self beConsistent.
63	aStream
64	    nextPutAll: 'An instance of ';
65	    print: self class;
66	    nl.
67	instVars := self class allInstVarNames.
68	1 to: instVars size
69	    do:
70		[:i |
71		object := self instVarAt: i.
72		output := [object printString] on: Error
73			    do:
74				[:ex |
75				ex
76				    return: '%1 %2' %
77						{object class article.
78						object class name asString}].
79		aStream
80		    nextPutAll: '  ';
81		    nextPutAll: (instVars at: i);
82		    nextPutAll: ': ';
83		    nextPutAll: output;
84		    nl].
85	aStream
86	    nextPutAll: '  contents: [';
87	    nl.
88	self keysAndValuesDo:
89		[:i :obj |
90		| output |
91		output := [obj printString] on: Error
92			    do:
93				[:ex |
94				ex
95				    return: '%1 %2' %
96						{obj class article.
97						obj class name asString}].
98		aStream
99		    nextPutAll: '    [';
100		    print: i;
101		    nextPutAll: ']: ';
102		    nextPutAll: output;
103		    nl].
104	aStream
105	    nextPutAll: '  ]';
106	    nl
107    ]
108
109    isSequenceable [
110	"Answer whether the receiver can be accessed by a numeric index with
111	 #at:/#at:put:."
112
113	<category: 'testing'>
114	^true
115    ]
116
117    = aCollection [
118	"Answer whether the receiver's items match those in aCollection"
119
120	<category: 'testing'>
121	self class == aCollection class ifFalse: [^false].
122	self size = aCollection size ifFalse: [^false].
123	1 to: self size
124	    do: [:i | (self at: i) = (aCollection at: i) ifFalse: [^false]].
125	^true
126    ]
127
128    hash [
129	"Answer an hash value for the receiver"
130
131	"Don't like this hash function; it can be made much better"
132
133	<category: 'testing'>
134	| hash carry |
135	hash := self size.
136	self do:
137		[:element |
138		carry := (hash bitAnd: 536870912) > 0.
139		hash := hash bitAnd: 536870911.
140		hash := hash bitShift: 1.
141		carry ifTrue: [hash := hash bitOr: 1].
142		hash := hash bitXor: element hash].
143	^hash
144    ]
145
146    endsWith: aSequenceableCollection [
147	"Returns true if the receiver ends with the same characters as aSequenceableCollection."
148
149	<category: 'comparing'>
150	| delta |
151	delta := self size - aSequenceableCollection size.
152	delta >= 0 ifFalse: [ ^false ].
153	aSequenceableCollection
154	    keysAndValuesDo: [:i :each |
155		(self at: i + delta) = each ifFalse: [^false]].
156	^true
157    ]
158
159    startsWith: aSequenceableCollection [
160	"Returns true if the receiver starts with the same characters as aSequenceableCollection."
161
162	<category: 'comparing'>
163	self size >= aSequenceableCollection size ifFalse: [ ^false ].
164	aSequenceableCollection
165	    keysAndValuesDo: [:i :each |
166		(self at: i) = each ifFalse: [^false]].
167	^true
168    ]
169
170    at: anIndex ifAbsent: aBlock [
171	"Answer the anIndex-th item of the collection, or evaluate aBlock
172	 and answer the result if the index is out of range"
173
174	<category: 'basic'>
175	(anIndex between: 1 and: self size) ifFalse: [^aBlock value].
176	^self at: anIndex
177    ]
178
179    atRandom [
180	"Return a random item of the receiver."
181
182	<category: 'basic'>
183	^self at: (Random between: 1 and: self size)
184    ]
185
186    atAll: keyCollection [
187	"Answer a collection of the same kind returned by #collect:, that
188	 only includes the values at the given indices. Fail if any of
189	 the values in keyCollection is out of bounds for the receiver."
190
191	<category: 'basic'>
192	| result |
193	result := self copyEmptyForCollect: keyCollection size.
194	keyCollection do: [:key | result add: (self at: key)].
195	^result
196    ]
197
198    atAll: aCollection put: anObject [
199	"Put anObject at every index contained in aCollection"
200
201	<category: 'basic'>
202	aCollection do: [:index | self at: index put: anObject]
203    ]
204
205    atAllPut: anObject [
206	"Put anObject at every index in the receiver"
207
208	<category: 'basic'>
209
210        | to size |
211        "Unroll completely for small collections..."
212        (size := self size) = 0 ifTrue: [ ^self ].
213        self at: 1 put: anObject. size = 1 ifTrue: [ ^self ].
214        self at: 2 put: anObject. size = 2 ifTrue: [ ^self ].
215        self at: 3 put: anObject. size = 3 ifTrue: [ ^self ].
216        self at: 4 put: anObject. to := 4.
217
218        "... and use memcpy repeatedly for larger ones."
219        [ size > to ] whileTrue: [
220            self
221                replaceFrom: to + 1
222                to: ((to := to + to) min: size)
223                with: self
224                startingAt: 1 ].
225    ]
226
227    after: oldObject [
228	"Return the element after oldObject.  Error if oldObject not found or
229	 if no following object is available"
230
231	<category: 'basic'>
232	| i |
233	i := self indexOf: oldObject.
234	i = 0
235	    ifTrue: [^SystemExceptions.NotFound signalOn: oldObject what: 'object'].
236	^self at: i + 1
237    ]
238
239    before: oldObject [
240	"Return the element before oldObject.  Error if oldObject not found or
241	 if no preceding object is available"
242
243	<category: 'basic'>
244	| i |
245	i := self indexOf: oldObject.
246	i = 0
247	    ifTrue: [^SystemExceptions.NotFound signalOn: oldObject what: 'object'].
248	^self at: i - 1
249    ]
250
251    allButFirst [
252	"Answer a copy of the receiver without the first object."
253
254	<category: 'basic'>
255	^self copyFrom: 2
256    ]
257
258    allButFirst: n [
259	"Answer a copy of the receiver without the first n objects."
260
261	<category: 'basic'>
262	^self copyFrom: n + 1
263    ]
264
265    allButLast [
266	"Answer a copy of the receiver without the last object."
267
268	<category: 'basic'>
269	^self copyFrom: 1 to: self size - 1
270    ]
271
272    allButLast: n [
273	"Answer a copy of the receiver without the last n objects."
274
275	<category: 'basic'>
276	^self copyFrom: 1 to: self size - n
277    ]
278
279    first [
280	"Answer the first item in the receiver"
281
282	<category: 'basic'>
283	^self at: 1
284    ]
285
286    second [
287	"Answer the second item in the receiver"
288
289	<category: 'basic'>
290	^self at: 2
291    ]
292
293    third [
294	"Answer the third item in the receiver"
295
296	<category: 'basic'>
297	^self at: 3
298    ]
299
300    fourth [
301	"Answer the fourth item in the receiver"
302
303	<category: 'basic'>
304	^self at: 4
305    ]
306
307    first: n [
308	"Answer the first n items in the receiver"
309
310	<category: 'basic'>
311	^self copyFrom: 1 to: n
312    ]
313
314    last: n [
315	"Answer the last n items in the receiver"
316
317	<category: 'basic'>
318	^self copyFrom: self size - n + 1
319    ]
320
321    last [
322	"Answer the last item in the receiver"
323
324	<category: 'basic'>
325	^self at: self size
326    ]
327
328    includes: anObject [
329	"Answer whether we include anObject"
330
331	"Reimplemented to avoid an expensive full-block"
332
333	<category: 'basic'>
334	1 to: self size do: [:index | anObject = (self at: index) ifTrue: [^true]].
335	^false
336    ]
337
338    identityIncludes: anObject [
339	"Answer whether we include the anObject object"
340
341	"Reimplemented to avoid an expensive full-block"
342
343	<category: 'basic'>
344	1 to: self size do: [:index | anObject == (self at: index) ifTrue: [^true]].
345	^false
346    ]
347
348    indexOfSubCollection: aSubCollection startingAt: anIndex ifAbsent: exceptionBlock [
349	"Answer the first index > anIndex at which starts a sequence of
350	 items matching aSubCollection.
351	 Invoke exceptionBlock and answer its result if no such sequence is found"
352
353	<category: 'basic'>
354	| selfSize subSize |
355	subSize := aSubCollection size.
356        subSize = 0 ifTrue: [ ^anIndex ].
357	selfSize := self size.
358	anIndex + subSize - 1 <= selfSize
359	    ifTrue:
360		[anIndex to: selfSize - subSize + 1
361		    do:
362			[:index |
363			(self at: index) = (aSubCollection at: 1)
364			    ifTrue:
365				[(self matchSubCollection: aSubCollection startingAt: index)
366				    ifTrue: [^index]]]].
367	^exceptionBlock value
368    ]
369
370    indexOfSubCollection: aSubCollection startingAt: anIndex [
371	"Answer the first index > anIndex at which starts a sequence of
372	 items matching aSubCollection. Answer 0 if no such sequence is found."
373
374	<category: 'basic'>
375	^self
376	    indexOfSubCollection: aSubCollection
377	    startingAt: anIndex
378	    ifAbsent: [^0]
379    ]
380
381    indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock [
382	"Answer the first index > anIndex which contains anElement.
383	 Invoke exceptionBlock and answer its result if no item is found"
384
385	<category: 'basic'>
386	anIndex < 1 | (anIndex > self size)
387	    ifTrue:
388		["If anIndex is just past the end of the collection, don't raise
389		 an error (this is the most generic solution that avoids that
390		 #indexOf: fails when the collection is empty."
391
392		anIndex = (self size + 1)
393		    ifTrue: [^exceptionBlock value]
394		    ifFalse: [^self checkIndexableBounds: anIndex]].
395	anIndex to: self size
396	    do: [:index | (self at: index) = anElement ifTrue: [^index]].
397	^exceptionBlock value
398    ]
399
400    identityIndexOf: anObject startingAt: anIndex ifAbsent: exceptionBlock [
401	"Answer the first index > anIndex which contains an object exactly
402	 identical to anObject.
403	 Invoke exceptionBlock and answer its result if no item is found"
404
405	<category: 'basic'>
406	anIndex < 1 | (anIndex > self size)
407	    ifTrue:
408		["If anIndex is just past the end of the collection, don't raise
409		 an error (this is the most generic solution that avoids that
410		 #indexOf: fails when the collection is empty."
411
412		anIndex = (self size + 1)
413		    ifTrue: [^exceptionBlock value]
414		    ifFalse: [^self checkIndexableBounds: anIndex]].
415	anIndex to: self size
416	    do: [:index | (self at: index) == anObject ifTrue: [^index]].
417	^exceptionBlock value
418    ]
419
420    indexOfSubCollection: aSubCollection [
421	"Answer the first index > anIndex at which starts a sequence of
422	 items matching aSubCollection. Answer 0 if no such sequence is found."
423
424	<category: 'basic'>
425	^self
426	    indexOfSubCollection: aSubCollection
427	    startingAt: 1
428	    ifAbsent: [^0]
429    ]
430
431    indexOfSubCollection: aSubCollection ifAbsent: exceptionBlock [
432	"Answer the first index > anIndex at which starts a sequence of
433	 items matching aSubCollection. Answer 0 if no such sequence is found."
434
435	<category: 'basic'>
436	^self
437	    indexOfSubCollection: aSubCollection
438	    startingAt: 1
439	    ifAbsent: exceptionBlock
440    ]
441
442    indexOf: anElement startingAt: anIndex [
443	"Answer the first index > anIndex which contains anElement.
444	 Answer 0 if no item is found"
445
446	<category: 'basic'>
447	^self
448	    indexOf: anElement
449	    startingAt: anIndex
450	    ifAbsent: [^0]
451    ]
452
453    identityIndexOfLast: anElement ifAbsent: exceptionBlock [
454	"Answer the last index which contains an object identical to anElement.
455	 Invoke exceptionBlock and answer its result if no item is found"
456
457	<category: 'basic'>
458	self size to: 1 by: -1
459	    do: [:index | (self at: index) == anElement ifTrue: [^index]].
460	^exceptionBlock value
461    ]
462
463    indexOfLast: anElement ifAbsent: exceptionBlock [
464	"Answer the last index which contains anElement.
465	 Invoke exceptionBlock and answer its result if no item is found"
466
467	<category: 'basic'>
468	self size to: 1 by: -1
469	    do: [:index | (self at: index) = anElement ifTrue: [^index]].
470	^exceptionBlock value
471    ]
472
473    indexOf: anElement ifAbsent: exceptionBlock [
474	"Answer the index of the first occurrence of anElement in the receiver.
475	 Invoke exceptionBlock and answer its result if no item is found"
476
477	<category: 'basic'>
478	^self
479	    indexOf: anElement
480	    startingAt: 1
481	    ifAbsent: exceptionBlock
482    ]
483
484    indexOf: anElement [
485	"Answer the index of the first occurrence of anElement in the receiver.
486	 Answer 0 if no item is found"
487
488	<category: 'basic'>
489	^self
490	    indexOf: anElement
491	    startingAt: 1
492	    ifAbsent: [^0]
493    ]
494
495    identityIndexOf: anElement startingAt: anIndex [
496	"Answer the first index > anIndex which contains an object identical
497	 to anElement. Answer 0 if no item is found"
498
499	<category: 'basic'>
500	^self
501	    identityIndexOf: anElement
502	    startingAt: anIndex
503	    ifAbsent: [^0]
504    ]
505
506    identityIndexOf: anElement ifAbsent: exceptionBlock [
507	"Answer the index of the first occurrence of an object identical to
508	 anElement in the receiver. Invoke exceptionBlock and answer its
509	 result if no item is found"
510
511	<category: 'basic'>
512	^self
513	    identityIndexOf: anElement
514	    startingAt: 1
515	    ifAbsent: exceptionBlock
516    ]
517
518    identityIndexOf: anElement [
519	"Answer the index of the first occurrence of an object identical to
520	 anElement in the receiver. Answer 0 if no item is found"
521
522	<category: 'basic'>
523	^self
524	    identityIndexOf: anElement
525	    startingAt: 1
526	    ifAbsent: [^0]
527    ]
528
529    replaceAll: anObject with: anotherObject [
530	"In the receiver, replace every occurrence of anObject with anotherObject."
531
532	<category: 'replacing items'>
533	1 to: self size
534	    do: [:index | (self at: index) = anObject ifTrue: [self at: index put: anotherObject]]
535    ]
536
537    replaceFrom: start to: stop with: replacementCollection startingAt: repStart [
538	"Replace the items from start to stop with replacementCollection's items
539	 from repStart to repStart+stop-start"
540
541	<category: 'replacing items'>
542	| delta maxStop minStop |
543	minStop := start - 1.
544	maxStop := self size min: minStop + replacementCollection size.
545	(minStop <= stop and: [stop <= maxStop])
546	    ifFalse:
547		[^SystemExceptions.ArgumentOutOfRange
548		    signalOn: stop
549		    mustBeBetween: minStop
550		    and: maxStop].
551	delta := start - repStart.
552	repStart > start
553	    ifTrue: [
554		start to: stop do: [:i |
555		    self at: i put: (replacementCollection at: i - delta)] ]
556	    ifFalse: [
557		stop to: start by: -1 do: [:i |
558		    self at: i put: (replacementCollection at: i - delta)] ]
559    ]
560
561    replaceFrom: start to: stop with: replacementCollection [
562	"Replace the items from start to stop with replacementCollection's items
563	 from 1 to stop-start+1 (in unexpected order if the collection is not
564	 sequenceable)."
565
566	<category: 'replacing items'>
567	| i |
568	i := start - 1.
569	stop - i = replacementCollection size
570	    ifFalse: [^SystemExceptions.InvalidSize signalOn: replacementCollection size].
571        replacementCollection isSequenceable ifTrue: [
572	    ^self replaceFrom: start to: stop with: replacementCollection startingAt: 1 ].
573
574	replacementCollection do: [:each | self at: (i := i + 1) put: each]
575    ]
576
577    replaceFrom: anIndex to: stopIndex withObject: replacementObject [
578	"Replace every item from start to stop with replacementObject."
579
580	<category: 'replacing items'>
581	stopIndex - anIndex < -1
582	    ifTrue:
583		[^SystemExceptions.ArgumentOutOfRange
584		    signalOn: stopIndex
585		    mustBeBetween: anIndex
586		    and: self size].
587	anIndex to: stopIndex do: [:index | self at: index put: replacementObject]
588    ]
589
590    copyAfter: anObject [
591	"Answer a new collection holding all the elements of the receiver
592	 after the first occurrence of anObject, up to the last."
593
594	<category: 'copying SequenceableCollections'>
595	^self copyFrom: (self indexOf: anObject ifAbsent: [self size]) + 1
596    ]
597
598    copyAfterLast: anObject [
599	"Answer a new collection holding all the elements of the receiver
600	 after the last occurrence of anObject, up to the last."
601
602	<category: 'copying SequenceableCollections'>
603	^self copyFrom: (self indexOfLast: anObject ifAbsent: [self size]) + 1
604    ]
605
606    copyUpTo: anObject [
607	"Answer a new collection holding all the elements of the receiver
608	 from the first up to the first occurrence of anObject, excluded."
609
610	<category: 'copying SequenceableCollections'>
611	^self copyFrom: 1
612	    to: (self indexOf: anObject
613		    ifAbsent: [self size + 1]) - 1
614    ]
615
616    copyUpToLast: anObject [
617	"Answer a new collection holding all the elements of the receiver
618	 from the first up to the last occurrence of anObject, excluded."
619
620	<category: 'copying SequenceableCollections'>
621	^self copyFrom: 1
622	    to: (self indexOfLast: anObject
623		    ifAbsent: [self size + 1]) - 1
624    ]
625
626    copyReplaceFrom: start to: stop withObject: anObject [
627	"Answer a new collection of the same class as the receiver that contains the
628	 same elements as the receiver, in the same order, except for elements from
629	 index `start' to index `stop'.
630
631	 If start < stop, these are replaced by stop-start+1 copies of anObject.
632	 Instead, If start = (stop + 1), then every element of the receiver
633	 will be present in the answered copy; the operation will be an append if
634	 stop is equal to the size of the receiver or, if it is not, an insert before
635	 index `start'."
636
637	<category: 'copying SequenceableCollections'>
638	| newSize repSize result |
639	stop - start < -1
640	    ifTrue:
641		[^SystemExceptions.ArgumentOutOfRange
642		    signalOn: stop
643		    mustBeBetween: start - 1
644		    and: self size].
645	stop >= start
646	    ifTrue:
647		[^(self copy)
648		    atAll: (start to: stop) put: anObject;
649		    yourself].
650	newSize := self size - (stop - start).
651	result := self copyEmpty: newSize.
652	start > 1
653	    ifTrue:
654		[self
655		    from: 1
656		    to: start - 1
657		    do: [:each | result add: each]].
658	result add: anObject.
659	stop < self size
660	    ifTrue:
661		[self
662		    from: stop + 1
663		    to: self size
664		    do: [:each | result add: each]].
665	^result
666    ]
667
668    copyWithFirst: anObject [
669	"Answer a new collection holding all the elements of the receiver
670	 after the first occurrence of anObject, up to the last."
671
672	<category: 'copying SequenceableCollections'>
673	^self copyReplaceFrom: 1 to: 0 withObject: anObject
674    ]
675
676    copyFrom: start [
677	"Answer a new collection containing all the items in the receiver from the
678	 start-th."
679
680	<category: 'copying SequenceableCollections'>
681	^self copyFrom: start to: self size
682    ]
683
684    copyFrom: start to: stop [
685	"Answer a new collection containing all the items in the receiver from the
686	 start-th and to the stop-th"
687
688	<category: 'copying SequenceableCollections'>
689	| len coll |
690	stop < start
691	    ifTrue:
692		[stop = (start - 1) ifTrue: [^self copyEmpty: 0].
693		^SystemExceptions.ArgumentOutOfRange
694		    signalOn: stop
695		    mustBeBetween: start - 1
696		    and: self size].
697	len := stop - start + 1.
698	coll := self copyEmpty: len + 10.
699	self
700	    from: start
701	    to: stop
702	    do: [:each | coll add: each].
703	^coll
704    ]
705
706    copyReplaceAll: oldSubCollection with: newSubCollection [
707	"Answer a new collection in which all the sequences matching
708	 oldSubCollection are replaced with newSubCollection"
709
710	<category: 'copying SequenceableCollections'>
711	| numOld newCollection sizeDifference newSubSize oldSubSize oldStart copySize index |
712	numOld := self countSubCollectionOccurrencesOf: oldSubCollection.
713	newSubSize := newSubCollection size.
714	oldSubSize := oldSubCollection size.
715	sizeDifference := newSubSize - oldSubSize.
716	newCollection := self copyEmpty: self size + (sizeDifference * numOld).
717	oldStart := 1.
718
719	[index := self
720		    indexOfSubCollection: oldSubCollection
721		    startingAt: oldStart
722		    ifAbsent:
723			["Copy the remaining part of self onto the tail of the new collection."
724
725			self
726			    from: oldStart
727			    to: self size
728			    do: [:each | newCollection add: each].
729			^newCollection].
730	copySize := index - oldStart.
731	self
732	    from: oldStart
733	    to: oldStart + copySize - 1
734	    do: [:each | newCollection add: each].
735	newCollection addAll: newSubCollection.
736	oldStart := oldStart + copySize + oldSubSize]
737		repeat
738    ]
739
740    copyReplaceFrom: start to: stop with: replacementCollection [
741	"Answer a new collection of the same class as the receiver that contains the
742	 same elements as the receiver, in the same order, except for elements from
743	 index `start' to index `stop'.
744
745	 If start < stop, these are replaced by the contents of the
746	 replacementCollection.  Instead, If start = (stop + 1), like in
747	 `copyReplaceFrom: 4 to: 3 with: anArray', then every element of the receiver
748	 will be present in the answered copy; the operation will be an append if
749	 stop is equal to the size of the receiver or, if it is not, an insert before
750	 index `start'."
751
752	<category: 'copying SequenceableCollections'>
753	| newSize repSize result |
754	stop - start < -1
755	    ifTrue:
756		[^SystemExceptions.ArgumentOutOfRange
757		    signalOn: stop
758		    mustBeBetween: start - 1
759		    and: self size].
760	repSize := replacementCollection size.
761	newSize := self size + repSize - (stop - start + 1).
762	result := self copyEmpty: newSize.
763	start > 1
764	    ifTrue:
765		[self
766		    from: 1
767		    to: start - 1
768		    do: [:each | result add: each]].
769	result addAll: replacementCollection.
770	stop < self size
771	    ifTrue:
772		[self
773		    from: stop + 1
774		    to: self size
775		    do: [:each | result add: each]].
776	^result
777    ]
778
779    join: sepCollection [
780	"Answer a new collection like my first element, with all the
781	 elements (in order) of all my elements (which should be
782	 collections) separated by sepCollection.
783
784	 I use my first element instead of myself as a prototype because
785	 my elements are more likely to share the desired properties than
786	 I am, such as in:
787
788	 #('hello,' 'world') join: ' ' => 'hello, world'"
789
790	<category: 'concatenating'>
791	^self isEmpty
792	    ifTrue: [#()]
793	    ifFalse: [self first species join: self separatedBy: sepCollection]
794    ]
795
796    nextPutAllOn: aStream [
797	"Write all the objects in the receiver to aStream"
798
799	aStream next: self size putAll: self startingAt: 1
800    ]
801
802    readStream [
803	"Answer a ReadStream streaming on the receiver"
804
805	<category: 'enumerating'>
806	^ReadStream on: self
807    ]
808
809    readWriteStream [
810	"Answer a ReadWriteStream which streams on the receiver"
811
812	<category: 'enumerating'>
813	^ReadWriteStream on: self
814    ]
815
816    anyOne [
817	"Answer an unspecified element of the collection."
818
819	<category: 'enumerating'>
820	^self first
821    ]
822
823    do: aBlock [
824	"Evaluate aBlock for all the elements in the sequenceable collection"
825
826	<category: 'enumerating'>
827	1 to: self size do: [:i | aBlock value: (self at: i)]
828    ]
829
830    do: aBlock separatedBy: sepBlock [
831	"Evaluate aBlock for all the elements in the sequenceable collection.
832	 Between each element, evaluate sepBlock without parameters."
833
834	<category: 'enumerating'>
835	self isEmpty ifTrue: [^self].
836	aBlock value: (self at: 1).
837	2 to: self size
838	    do:
839		[:i |
840		sepBlock value.
841		aBlock value: (self at: i)]
842    ]
843
844    doWithIndex: aBlock [
845	"Evaluate aBlock for all the elements in the sequenceable collection,
846	 passing the index of each element as the second parameter.  This method
847	 is mantained for backwards compatibility and is not mandated by the
848	 ANSI standard; use #keysAndValuesDo:"
849
850	<category: 'enumerating'>
851	1 to: self size do: [:i | aBlock value: (self at: i) value: i]
852    ]
853
854    fold: binaryBlock [
855	"First, pass to binaryBlock the first and second elements of the
856	 receiver; for each subsequent element, pass the result of the previous
857	 evaluation and an element. Answer the result of the last invocation,
858	 or the first element if the collection has size 1.  Fail if the collection
859	 is empty."
860
861	"This method is redefined from Collection for efficiency only"
862
863	<category: 'enumerating'>
864	| result |
865	self isEmpty ifTrue: [^SystemExceptions.EmptyCollection signalOn: self].
866	result := self at: 1.
867	self
868	    from: 2
869	    to: self size
870	    do: [:element | result := binaryBlock value: result value: element].
871	^result
872    ]
873
874    keys [
875	"Return an Interval corresponding to the valid indices in the receiver."
876
877	<category: 'enumerating'>
878	^1 to: self size
879    ]
880
881    keysAndValuesDo: aBlock [
882	"Evaluate aBlock for all the elements in the sequenceable collection,
883	 passing the index of each element as the first parameter and the
884	 element as the second."
885
886	<category: 'enumerating'>
887	1 to: self size do: [:i | aBlock value: i value: (self at: i)]
888    ]
889
890    from: startIndex to: stopIndex do: aBlock [
891	"Evaluate aBlock for all the elements in the sequenceable collection whose
892	 indices are in the range index to stopIndex"
893
894	<category: 'enumerating'>
895	startIndex to: stopIndex do: [:i | aBlock value: (self at: i)]
896    ]
897
898    from: startIndex to: stopIndex doWithIndex: aBlock [
899	"Evaluate aBlock for all the elements in the sequenceable collection whose
900	 indices are in the range index to stopIndex, passing the index of each
901	 element as the second parameter.  This method is mantained for backwards
902	 compatibility and is not mandated by the ANSI standard; use
903	 #from:to:keysAndValuesDo:"
904
905	<category: 'enumerating'>
906	startIndex to: stopIndex do: [:i | aBlock value: (self at: i) value: i]
907    ]
908
909    from: startIndex to: stopIndex keysAndValuesDo: aBlock [
910	"Evaluate aBlock for all the elements in the sequenceable collection whose
911	 indices are in the range index to stopIndex, passing the index of each
912	 element as the first parameter and the element as the second."
913
914	<category: 'enumerating'>
915	startIndex to: stopIndex do: [:i | aBlock value: i value: (self at: i)]
916    ]
917
918    findFirst: aBlock [
919	"Returns the index of the first element of the sequenceable collection
920	 for which aBlock returns true, or 0 if none"
921
922	<category: 'enumerating'>
923	self doWithIndex: [:each :i | (aBlock value: each) ifTrue: [^i]].
924	^0
925    ]
926
927    findLast: aBlock [
928	"Returns the index of the last element of the sequenceable collection
929	 for which aBlock returns true, or 0 if none does"
930
931	<category: 'enumerating'>
932	| i |
933	i := self size.
934	self reverseDo:
935		[:each |
936		(aBlock value: each) ifTrue: [^i].
937		i := i - 1].
938	^0
939    ]
940
941    reverse [
942	"Answer the receivers' contents in reverse order"
943
944	<category: 'enumerating'>
945	| result |
946	result := self copyEmptyForCollect.
947	self reverseDo: [:each | result add: each].
948	^result
949    ]
950
951    reverseDo: aBlock [
952	"Evaluate aBlock for all elements in the sequenceable collection, from the
953	 last to the first."
954
955	<category: 'enumerating'>
956	self size to: 1
957	    by: -1
958	    do: [:i | aBlock value: (self at: i)]
959    ]
960
961    with: aSequenceableCollection do: aBlock [
962	"Evaluate aBlock for each pair of elements took respectively from
963	 the receiver and from aSequenceableCollection. Fail if the receiver
964	 has not the same size as aSequenceableCollection."
965
966	<category: 'enumerating'>
967	self size = aSequenceableCollection size
968	    ifFalse: [^SystemExceptions.InvalidSize signalOn: aSequenceableCollection].
969	1 to: self size
970	    do: [:i | aBlock value: (self at: i) value: (aSequenceableCollection at: i)]
971    ]
972
973    with: aSequenceableCollection collect: aBlock [
974	"Evaluate aBlock for each pair of elements took respectively from
975	 the receiver and from aSequenceableCollection; answer a collection of
976	 the same kind of the receiver, made with the block's return values.
977	 Fail if the receiver has not the same size as aSequenceableCollection."
978
979	<category: 'enumerating'>
980	| newCollection |
981	self size = aSequenceableCollection size
982	    ifFalse: [^SystemExceptions.InvalidSize signalOn: aSequenceableCollection].
983	newCollection := self copyEmptyForCollect.
984	1 to: self size
985	    do:
986		[:i |
987		newCollection
988		    add: (aBlock value: (self at: i) value: (aSequenceableCollection at: i))].
989	^newCollection
990    ]
991
992    with: aSequenceableCollection [
993	"Return an Array with the same size as the receiver and
994	 aSequenceableCollection, each element of which is a 2-element
995	 Arrays including one element from the receiver and one from
996	 aSequenceableCollection."
997	<category: 'concatenating'>
998	self size = aSequenceableCollection size
999	    ifFalse: [^SystemExceptions.InvalidSize signalOn: aSequenceableCollection].
1000	^1 to: self size collect: [ :each |
1001	    { self at: each. aSequenceableCollection at: each } ]
1002    ]
1003
1004    with: seqColl1 with: seqColl2 [
1005	"Return an Array with the same size as the receiver and
1006	 the arguments, each element of which is a 3-element
1007	 Arrays including one element from the receiver and one from
1008	 each argument."
1009	<category: 'concatenating'>
1010	self size = seqColl1 size
1011	    ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl1].
1012	self size = seqColl2 size
1013	    ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl2].
1014	^1 to: self size collect: [ :each |
1015	    { self at: each. seqColl1 at: each. seqColl2 at: each } ]
1016    ]
1017
1018    with: seqColl1 with: seqColl2 with: seqColl3 [
1019	"Return an Array with the same size as the receiver and
1020	 the arguments, each element of which is a 4-element
1021	 Arrays including one element from the receiver and one from
1022	 each argument."
1023	<category: 'concatenating'>
1024	self size = seqColl1 size
1025	    ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl1].
1026	self size = seqColl2 size
1027	    ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl2].
1028	self size = seqColl3 size
1029	    ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl3].
1030	^1 to: self size collect: [ :each |
1031	    { self at: each. seqColl1 at: each. seqColl2 at: each.
1032	      seqColl3 at: each } ]
1033    ]
1034
1035    sorted [
1036	"Return a copy of the receiver sorted according to the default
1037	 sort block, which uses #<= to compare items."
1038        <category: 'sorting'>
1039	^(self copyEmptyForCollect: self size)
1040	    addAll: self asSortedCollection;
1041	    yourself
1042    ]
1043
1044    sorted: sortBlock [
1045	"Return a copy of the receiver sorted according to the given
1046	 sort block, which accepts pair of items and returns true if
1047	 the first item is less than the second one."
1048        <category: 'sorting'>
1049	^(self copyEmptyForCollect: self size)
1050	    addAll: (self asSortedCollection: sortBlock);
1051	    yourself
1052    ]
1053
1054    sort [
1055	"Sort the contents of the receiver according to the default
1056	 sort block, which uses #<= to compare items."
1057        <category: 'sorting'>
1058	self
1059	    replaceFrom: 1
1060	    to: self size
1061	    with: self asSortedCollection
1062	    startingAt: 1
1063    ]
1064
1065    sort: sortBlock [
1066	"Sort the contents of the receiver according to the given
1067	 sort block, which accepts pair of items and returns true if
1068	 the first item is less than the second one."
1069        <category: 'sorting'>
1070	self
1071	    replaceFrom: 1
1072	    to: self size
1073	    with: (self asSortedCollection: sortBlock)
1074	    startingAt: 1
1075    ]
1076
1077    matchSubCollection: aSubCollection startingAt: anIndex [
1078	"Private - Answer whether the items from index anIndex match those in
1079	 aSubCollection. The first item is ignored"
1080
1081	<category: 'private methods'>
1082	| ourIndex |
1083	ourIndex := anIndex.
1084	2 to: aSubCollection size
1085	    do:
1086		[:index |
1087		ourIndex := ourIndex + 1.
1088		(self at: ourIndex) = (aSubCollection at: index) ifFalse: [^false]].
1089	^true
1090    ]
1091
1092    countSubCollectionOccurrencesOf: aSubCollection [
1093	<category: 'private methods'>
1094	| colIndex subColIndex count |
1095	colIndex := 1.
1096	count := 0.
1097
1098	[subColIndex := self indexOfSubCollection: aSubCollection
1099		    startingAt: colIndex.
1100	subColIndex > 0]
1101		whileTrue:
1102		    [count := count + 1.
1103		    colIndex := subColIndex + aSubCollection size].
1104	^count
1105    ]
1106
1107    size [
1108	"Answer a dummy size of 0, so that SequenceableCollection>>#do: works."
1109
1110	<category: 'testing collections'>
1111	^0
1112    ]
1113
1114    growSize [
1115	<category: 'private methods'>
1116	^(self size max: 8)
1117    ]
1118
1119    swap: anIndex with: anotherIndex [
1120	"Swap the item at index anIndex with the item at index
1121	 another index"
1122
1123	<category: 'manipulation'>
1124	| saved |
1125	saved := self at: anIndex.
1126	self at: anIndex put: (self at: anotherIndex).
1127	self at: anotherIndex put: saved
1128    ]
1129
1130]
1131
1132