Revert "Revert "Core code source usage of ::= and other cleanups.""
[cslatevm.git] / src / core / stream-collections.slate
blob68ceefdca30c0a12d8c4faaefa25e3a1e82818f5
1 Collection traits define: #Stream &parents: {PositionableStream} &slots: {#collection}.
2 "Collection Streams allow accessing of and writing into Collections like any
3 other Stream terminal."
5 s@(Collection Stream traits) terminal [s collection].
7 s@(Collection Stream traits) contents
8 "Answer the Stream's contents, in the default case the collection itself."
10   s collection
13 s@(Collection Stream traits) close
14 "Closes the link between the Stream and the Collection and resets it,
15 returning the Collection."
16 [| result |
17   result := s collection.
18   s collection := Nil.
19   s reset.
20   result
23 s@(Collection Stream traits) hasAnEnd
24 "All Collections are finite, so Streams over them have an end."
25 [True].
27 s@(Collection Stream traits) collectionType
28 [#{}].
30 streamBlock@(Method traits) writingInto: c@(Collection traits)
31 "Create a new WriteStream for the given collection and apply the block to it,
32 answering the contents once done."
33 [| stream |
34   stream := c writer.
35   streamBlock applyWith: stream.
36   stream contents
39 streamBlock@(Method traits) writingAs: c@(Collection traits) &capacity: capacity
40 "Create a new WriteStream for a new collection like the given one and apply the
41 block to it, answering the contents once done."
43   streamBlock writingInto: (c new &capacity: capacity)
46 streamBlock@(Method traits) writingAs: s@(ReadStream traits) &capacity: capacity
48   (streamBlock writingAs: s contents new &capacity: capacity) reader
51 Collection traits define: #ReadStream
52                   &parents: {Collection Stream. ReadStream}.
53 "The default kind of iterator, a slot on the shared traits of Collection."
55 ExtensibleCollection traits define: #WriteStream &parents: {WriteStream} &slots: {#collection}.
56 "A totally non-Positionable WriteStream variant which just maps the protocol
57 to Collection addition protocol."
59 ws@(ExtensibleCollection WriteStream traits) on: c
60 "Targets the collection."
62   ws collection := c.
63   ws
66 ws@(ExtensibleCollection WriteStream traits) contents
68   ws collection
71 ws@(ExtensibleCollection WriteStream traits) nextPut: obj
72 [ws collection add: obj].
74 ws@(ExtensibleCollection WriteStream traits) nextPutAll: c
75 [ws collection addAll: c].
77 ws@(ExtensibleCollection WriteStream traits) next: n putAll: seq startingAt: start
79   ws collection addAll: (seq sliceFrom: start)
82 ws@(ExtensibleCollection WriteStream traits) close
83 "Closes the link between the Stream and the Collection and resets it."
84 [| result |
85   result := ws collection.
86   ws collection := Nil.
87   result
90 ws@(ExtensibleCollection WriteStream traits) hasAnEnd [True].
92 ws@(ExtensibleCollection WriteStream traits) isAtEnd
93 "This type of stream cannot write over the contents and is perpetually
94 `at the end' of the contents, adding new elements."
95 [True].
97 c@(Collection traits) iterator
98 "Syntactic sugar for getting a new ReadStream or ReadWriteStream over the
99 given Collection that respects the same type."
100 [c reader].
102 c@(Collection traits) reader
103 "Syntactic sugar for getting a new ReadStream onto the given Collection
104 that respects the same type."
105 [c ReadStream newOn: c].
107 c@(Collection traits) writer
108 "Syntactic sugar for getting a new WriteStream onto the given Collection
109 that respects the same type."
110 [c WriteStream newOn: c].
112 cols@(Collection traits) iterators
113 "Returns a Collection of ReadStreams on the those in the given one. The
114 argument collection cannot contain non-collections."
116   cols collect: #iterator `er into: Array
119 cols@(Sequence traits) allDo: block
120 "Apply a coordinated do: over all of the collections in the given one,
121 using iterators."
123   iterators ::= cols iterators.
124   args ::= Array newSizeOf: iterators.
125   [iterators anySatisfy: #isAtEnd `er]
126     whileFalse:
127       [iterators collect: #next `er into: args.
128        block applyTo: args].
131 x@(Collection traits) with: y@(Collection traits) do: block
132 [{x. y} allDo: block].
134 cols@(Sequence traits) allCollect: block into: result
135 "Uses allDo: to perform a collect: over the Sequence's Collections' elements,
136 using a stream in between."
137 [[| :result | cols allDo: [| *vals | result nextPut: (block applyTo: vals)]]
138   writingAs: result
141 cols@(Sequence traits) allCollect: block
142 "Perform allCollect:into: using the Sequence as the result template."
143 [cols allCollect: block into: cols].
145 cols@(Sequence traits) streamAllCollect: block
147   [(cols iterators collect: #next`er)
148      reader collect: [| *rest | block applyTo: rest]]
149     breakOn: Exhaustion
152 x@(Collection traits) with: y@(Collection traits) collect: block
153 [{x. y} allCollect: block].
155 cols@(Sequence traits) zip
156 "Uses allCollect: to gather all the collection's collections' elements into
157 one collection. In other words, zip means to turn a pair of lists into
158 a list of pairs (for general values of 'pair')."
159 [cols allCollect: [| *vals | vals]].
161 cols@(Sequence traits) unzip
162 "Transposes a sequence of collection into a collection of sequences of those
163 elements across them, using a collection of streams and running with:do:
164 across the collection-result mapping. In other words, unzip means to turn a
165 list of pairs into a pair of lists (for general values of 'pair')."
167   results ::= cols first collect: [| :_ | cols newSameSize writer].
168   cols do:
169     [| :col | col with: results do: [| :val :result | result nextPut: val]].
170   results collect: #contents `er
173 cols@(Sequence traits) allInject: start into: block
174 "Runs inject:into: across all the given collection's collections' elements."
175 [| result |
176   result := start.
177   cols allDo: [| *vals | result := block applyTo: (vals copyWith: result at: 0)].
178   result
181 source@(Root traits) streamInto: target
182 "Totally generic method for streaming the contents of one thing into another."
184   source reader >> target writer
187 source@(Root traits) streamFrom: target
189   target streamInto: source
192 cols@(Sequence traits) combinationsDo: block
193 "This performs a basic increment-with-carry across the iterators until
194 they are exhausted. The block is applied to all intermediate results."
195 [| position it |
196   ((iterators ::= cols iterators) anySatisfy: #isAtEnd `er)
197    ifTrue: [^ Nil].
198   values ::= iterators collect: #next `er .
199   block applyTo: values.
200   [position := iterators indexLast.
201    eachIterator := iterators at: position.
202    [eachIterator isAtEnd /\ [position > 0]]
203      whileTrue:
204        [eachIterator reset.
205         values at: position put: eachIterator next.
206         position -= 1.
207         eachIterator := iterators at: position].
208    eachIterator isAtEnd /\ [position isZero]
209      ifTrue:
210        [^ Nil]
211      ifFalse:
212        [values at: position put: eachIterator next].
213    block applyTo: values] loop
216 cols@(Sequence traits) combinationsCollect: block into: result
217 "Uses combinationsDo: to perform a collect: over all combinations of elements from the
218 Collections in the Sequence, using a stream in between."
219 [[| :result | cols combinationsDo: [| *vals | result nextPut: (block applyTo: vals)]]
220   writingAs: result
223 cols@(Sequence traits) combinationsCollect: block
224 "Perform combinationsCollect:into: using the Sequence as the result template."
225 [cols combinationsCollect: block into: cols].
227 cols@(Sequence traits) combinationsInject: start into: block
228 "Runs inject:into: across all the combinations of the given Sequence's Collections' elements."
229 [| result |
230   result := start.
231   cols combinationsDo: [| *vals | result := block applyTo: (vals copyWith: result at: 0)].
232   result
235 Set traits define: #ReadStream &parents: {Collection ReadStream} &slots: {
236   #collection -> Set new.
237   #position -> 0. "The number of elements passed so far."
238   #index -> 0. "The index into the Set's contents Array."
240 "Set ReadStreams are just Positionable- over the element order in the Set's
241 contents Array. They're not very efficient, having to check for Nil's."
243 i@(Set ReadStream traits) on: c
244 "Retargets to the new Set, and resets position, etc."
245 [i `>> [collection := c. position := 0. index := 0. ]].
247 i@(Set ReadStream traits) next
248 "Increment the index through the array until a non-Nil element is reached.
249 This is poor for sparse Sets."
251   (i collection contents indexOfFirstSatisfying: [| :x | x isNotNil] startingAt: i index)
252     ifNil: [i exhausted]
253     ifNotNilDo:
254       [| :nextIndex |
255        i index := nextIndex + 1.
256        i position := i position + 1.
257        i collection contents at: nextIndex]
260 i@(Set ReadStream traits) next: n putInto: seq startingAt: start
261 [| numRead contents nextIndex |
262   numRead := 0.
263   contents := i collection contents.
264   nextIndex := i index.
265   seqIndex := start.
266   [(nextIndex := contents indexOfFirstSatisfying: #isNotNil `er startingAt: i index) isNil] whileFalse:
267     [i index := nextIndex + 1.
268      i position := i position + 1.
269      seq at: seqIndex put: (contents at: nextIndex).
270      seqIndex += 1].
271   numRead
274 i@(Set ReadStream traits) isAtEnd
275 "Checks both the Set size and then the underlying Array index, since a sparse
276 Set would reach the first before the second."
278   i position = i collection size \/ [i index = i collection contents indexLast]
281 Sequence traits define: #Stream &parents: {PositionableStream} &slots: {#collection -> ExtensibleArray new}.
282 "A Stream over a Sequence, where the position corresponds to the index within
283 the Sequence."
285 s@(Sequence Stream traits) on: c
286 "Target the stream to the specific collection, and reset the indices."
287 [s `>> [reset. collection := c. readLimit := c size. ]].
289 s@(Sequence Stream traits) contents
290 "Answer the contents of the target by copying, up to the limit."
292   s collection copyFrom: 0 below: s readLimit
295 s@(Sequence Stream traits) collectionType
296 [s collection].
298 s@(Sequence Stream traits) last
300   s collection at: s position
303 Sequence traits define: #ReadStream
304   &parents: {Sequence Stream. ReadStream}.
305 "A Stream used to read from a Sequence object."
307 s@(Stream traits) newFrom: obj
308 "A convenient method to override for creating new ReadStreams of the
309 appropriate type for a given type of object."
310 "NOTE: determine what overrides justify this since #reader is easier for nearly
311 all cases."
312 [obj ReadStream newOn: obj].
314 rs@(Sequence ReadStream traits) next
315 [| pos |
316   (pos := rs position) < rs readLimit
317     ifTrue:
318       [rs position := pos + 1.
319        rs collection at: pos]
320     ifFalse: [rs exhausted]
323 rs@(Sequence ReadStream traits) next: n
324 "Overridden for efficiency."
325 [| newC end |
326   end := rs position + n min: rs readLimit.
327   newC := rs collection copyFrom: rs position below: end.
328   rs position := end.
329   newC
332 rs@(Sequence ReadStream traits) next: n putInto: c startingAt: start
333 [| max |
334   max := rs readLimit - rs position min: n.
335   c replaceFrom: start to: start + max - 1 with: rs collection startingAt: rs position.
336   rs position := rs position + max.
337   max
340 rs@(Sequence ReadStream traits) peekAt: offset
342   rs collection at: rs position + offset
345 rs@(Sequence ReadStream traits) peek
346 [rs peekAt: 0].
348 rs@(Sequence ReadStream traits) peekBack
350   rs position isZero ifFalse: [rs position := rs position - 1. rs next]
353 rs@(Sequence ReadStream traits) nextPut: obj
354 "Sequence ReadStreams should not place elements into the stream."
355 [Nil].
357 rs@(Sequence ReadStream traits) size
358 "The limit is effectively the number of elements that can be collected."
360   rs readLimit
363 rs@(Sequence ReadStream traits) upTo: obj
364 "Answer all the elements until the given object is reached."
365 [| start end |
366   start := rs position.
367   end := rs collection indexOf: obj startingAt: start
368     ifAbsent: [rs position := rs collection size. ^ (rs collection copyFrom: start)].
369   rs position := end + 1.
370   rs collection copyFrom: start below: end
373 rs@(Sequence ReadStream traits) upToEnd
374 "Answer all the elements up to the limit by a copy."
375 [| start |
376   start := rs position.
377   rs position := rs collection size.
378   rs collection copyFrom: start below: rs position
381 rs@(Sequence ReadStream traits) on: c from: start to: end
382 "Target the stream on a particular slice of a collection."
383 [rs `>> [collection := c. readLimit := end min: c size. position := start. ]].
385 Sequence traits define: #WriteStream
386                 &parents: {Sequence Stream. WriteStream}
387                 &slots: {#writeLimit}.
389 s@(Stream traits) newTo: obj@(Sequence traits) &position: position
390 [obj WriteStream newOn: obj &position: position].
392 seq@(Sequence traits) writer &position: position
393 [seq WriteStream newOn: seq &position: position].
395 seq@(Sequence traits) appender
396 [seq WriteStream newOn: seq &position: seq size].
398 ws@(Sequence WriteStream traits) newOn: c &position: position
399 [ws clone on: c &position: position].
401 ws@(Sequence WriteStream traits) on: c &position: position
403   resend.
404   ws writeLimit := c size.
405   position ifNotNil: [ws position := position].
406   ws
409 ws@(Sequence WriteStream traits) contents
411   ws readLimit := ws readLimit max: ws position.
412   ws collection copyFrom: 0 below: ws readLimit
415 ws@(Sequence WriteStream traits) next
416 [Nil].
418 ws@(Sequence WriteStream traits) growCollectionAtEnd &byAtLeast: minGrowth
419 [| c newSize |
420   c := ws collection.
421   newSize := c size + (c size min: 1000000 max: (minGrowth ifNil: [20])).
422   ws collection := c newSize: newSize.
423   ws collection replaceFrom: 0 to: c size - 1 with: c.
424   ws writeLimit := newSize.
427 ws@(Sequence WriteStream traits) pastEndPut: obj
429   ws growCollectionAtEnd.
430   ws collection at: ws position put: obj.
431   ws position := ws position + 1.
432   obj
435 ws@(Sequence WriteStream traits) nextPut: obj
436 [| pos |
437   (pos := ws position) >= ws writeLimit
438     ifTrue: [ws pastEndPut: obj]
439     ifFalse: [ws position := pos + 1.
440               ws collection at: pos put: obj]
443 ws@(Sequence WriteStream traits) next: n putAll: c startingAt: start
444 [| newEnd |
445   (newEnd := ws position + n - 1) >= ws writeLimit ifTrue:
446     [ws growCollectionAtEnd &byAtLeast: newEnd - ws writeLimit + 4].
447   ws collection replaceFrom: ws position to: newEnd with: c startingAt: start.
448   ws position := newEnd + 1.
449   n
452 ws@(Sequence WriteStream traits) size
454   ws readLimit := ws readLimit max: ws position
457 ws@(Sequence WriteStream traits) position: n
459   ws readLimit := ws readLimit max: n.
460   resend.
461   ws
464 ws@(Sequence WriteStream traits) newLine
465 "Output an appropriate newLine character."
466 "TODO: make this portable."
468   ws nextPut: $\n
471 ws@(Sequence WriteStream traits) atBeginningOfLine
472 "Returns whether the stream is writing at a point where a line ending has
473 just occurred."
474 "TODO: make this portable."
476   (ws collection at: ws position - 1) = $\n
479 ws@(Sequence WriteStream traits) freshLine
480 "Output a newLine character character if not currently at the end of a line."
482   ws atBeginningOfLine ifFalse: [ws newLine]
485 ws@(Sequence WriteStream traits) reset
487   ws readLimit := ws readLimit max: ws position.
488   ws position := 0.
489   ws
492 ws@(Sequence WriteStream traits) resetToStart
494   ws readLimit := ws position := 0.
495   ws
498 ws@(Sequence WriteStream traits) setToEnd
500   ws position := ws size.
501   ws
504 ws@(Sequence WriteStream traits) on: c from: start to: end
506   ws collection := c.
507   ws readLimit := ws writeLimit := end min: c size.
508   ws position := start.
509   ws
512 ws@(Sequence WriteStream traits) peekLast
514   ws position ifNotNil: [ws contents at: position]
517 ws@(Sequence WriteStream traits) with: c
519   ws collection := c.
520   ws position := ws readLimit := ws writeLimit := c size.
521   ws
524 Sequence traits define: #ReadWriteStream
525                 &parents: {Sequence WriteStream. Sequence ReadStream}.
527 rws@(Sequence traits) iterator
529   rws ReadWriteStream newOn: rws
532 rws@(Sequence ReadWriteStream traits) contents
534   rws readLimit := rws readLimit max: rws position.
535   rws collection copyFrom: 0 below: rws readLimit
538 rws@(Sequence ReadWriteStream traits) next
539 [| pos |
540   (pos := rws position) >= rws readLimit
541     ifTrue: [rws exhausted]
542     ifFalse: [rws position := pos + 1.
543       rws collection at: pos]
546 rws@(Sequence ReadWriteStream traits) next: n
547 [| newC end |
548   rws readLimit := rws readLimit max: rws position.
549   end := rws position + n min: rws readLimit.
550   newC := rws collection copyFrom: rws position below: end.
551   rws position := end.
552   newC
555 rws@(Sequence ReadWriteStream traits) = rws2@(Sequence ReadWriteStream traits)
557   rws position = rws2 position /\ [rws contents = rws2 contents]
560 rws@(Sequence ReadWriteStream traits) hash
562   (rws isSameAs: Sequence ReadWriteStream) ifFalse: [^ resend].
563   (rws position + rws readLimit + 53) hash
566 ExtensibleSequence traits define: #WriteStream
567   &parents: {Sequence WriteStream}.
568 "A Stream used to write to a new or existing ExtensibleSequence."
570 ws@(ExtensibleSequence WriteStream traits) pastEndPut: obj
571 [| c |
572   c := ws collection.
573   c addLast: obj.
574   ws writeLimit := c size.
575   ws position := ws position + 1.
576   obj
579 ws@(ExtensibleSequence WriteStream traits) next: n putAll: c startingAt: start
581   ws collection at: ws position insertAll: (c copyFrom: start below: start + n).
582   ws position := ws position + n.
583   n
586 ExtensibleSequence traits define: #ReadWriteStream
587   &parents: {ExtensibleSequence WriteStream. ExtensibleSequence ReadStream}.