1 prototypes ensureNamespace: #streams &delegate: True.
3 streams define: #Stream &parents: {Cloneable}.
4 "The shared protocol of all Stream objects, also providing a common
5 instantiation protocol."
7 s@(Stream traits) newOn: c
8 "Create a new stream of the same kind targeted on the given object."
13 s@(Stream traits) on: _
14 "(Re-)target the stream to some object. This modifies it in-place.
15 Overriding this will also customize newOn: for most uses."
18 s@(Stream traits) flush
19 "Do nothing by default."
22 s@(Stream traits) isAtEnd
23 "Answer whether the end of the Stream has been reached."
26 s@(Stream traits) hasAnEnd
27 "Answer whether the Stream has a known end, i.e. will it ever isAtEnd."
30 s@(Stream traits) elementType
31 "Returns a prototype for an appropriate element type for the Stream. This is
32 the most generic type."
33 [s contents elementType].
35 s@(Stream traits) collectionType
36 "Returns a prototype for an appropriate array type for the Stream. This is
37 the most generic type."
40 s@(Stream traits) contents
41 "Answer what is conceptually being held or accumulated by the Stream."
44 Stream traits define: #Condition &parents: {SeriousCondition} &slots: {#stream}.
45 "Streaming-specific errors."
47 c@(Stream Condition traits) newFor: s
48 [c new `>> [stream := s. ]].
50 Stream traits define: #Exhaustion &parents: {Stream Condition. Error}.
51 "Stream or resource exhaustion, ie #isAtEnd Conditions."
53 e@(Stream Exhaustion traits) describeOn: out
55 out ; 'The stream has reached its end, unhandled.'
58 s@(Stream traits) exhausted
60 (s Exhaustion newFor: s) signal
63 s@(Stream traits) endCheck
65 s isAtEnd ifTrue: [s exhausted]
68 Stream traits define: #Incomplete &parents: {Stream Condition} &slots: {
74 i@(Stream Incomplete traits) on: c count: count at: start
76 i new `>> [collection := c. count := count. start := start. ]
79 i@(Stream Incomplete traits) zero
80 [i on: Nil count: 0 at: Nil].
82 i@(Stream Incomplete traits) contents
85 ifTrue: [i collection newSize: i count]
86 ifFalse: [i collection copyFrom: i start below: i start + count]
89 streams define: #ReadStream &parents: {Stream}.
90 "Streams that read from some source."
92 s@(ReadStream traits) reader
93 "A ReadStream is already its own resource."
96 s@(ReadStream traits) next: n putInteractivelyInto: seq startingAt: start
97 "Returns the number of objects successfully read."
101 (obj := s next) on: s Exhaustion do: [| :c | ^ index].
102 seq at: start + index put: obj].
106 s@(ReadStream traits) next: n putInto: seq startingAt: start
107 "Take the next N elements from the stream and write into the Sequence from
108 the given starting index."
111 s@(ReadStream traits) nextPutInto: seq startingAt: start
113 s next: seq size putInto: seq startingAt: start
116 s@(ReadStream traits) nextPutInto: seq
118 s next: seq size putInto: seq startingAt: 0
121 s@(ReadStream traits) next: n putInto: seq@(Sequence traits)
122 "Places the next N elements into a Sequence at the starting indices."
124 s next: n putInto: seq startingAt: 0
127 s@(ReadStream traits) next: n putInto: seq@(ExtensibleArray traits)
128 "Places the next N elements at the end of a given ExtensibleArray."
131 seq addAllLast: elems.
135 s@(ReadStream traits) next: n
136 "Answer the next N elements."
138 arr ::= s collectionType new &capacity: n.
139 (read ::= s next: n putInto: arr startingAt: 0)
140 = n ifTrue: [arr] ifFalse: [arr first: read]
143 s@(ReadStream traits) next
144 "Obtain and answer the next element from the Stream."
147 isEmpty ifTrue: [s exhausted] ifFalse: [arr first]
150 s@(ReadStream traits) numAvailable
151 "Answer the number of elements that can be read (currently)."
154 s@(ReadStream traits) advanceToSatisfying: testBlock
155 "Advance the stream to the first object that satisfies the block test."
157 [s isAtEnd \/ [testBlock applyWith: s next]] whileFalse
160 s@(ReadStream traits) upToSatisfying: testBlock
161 "Answer all objects and advance up to one satisfying the block test."
163 result ::= s collectionType new writer.
164 [s isAtEnd \/ [testBlock applyWith: (elem := s next)]]
165 whileFalse: [result nextPut: elem].
169 s@(ReadStream traits) upTo: obj
170 "Answer all objects and advance up to one equal to the argument."
171 [s upToSatisfying: #(= obj) `er].
173 s@(ReadStream traits) upToAnyOf: c@(Collection traits)
174 "Answer all objects and advance up to one contained by the argument."
175 [s upToSatisfying: #(c includes: _) `er].
177 s@(ReadStream traits) upToEnd
178 "Supply all the elements and advance up to the end of the stream."
181 [s isAtEnd] whileFalse: [result nextPut: s next]] writingAs: s collectionType
184 s@(ReadStream traits) nextLine
185 "Fixme: this should be more sophisticated for cross platform support"
187 result := s collectionType new writer.
188 [s isAtEnd \/ [(elem := s next). elem = $\n]]
189 whileFalse: [result nextPut: elem].
190 s isAtEnd ifFalse: [result nextPut: elem].
194 s@(ReadStream traits) do: block
195 "Call the block on all the elements in turn until the Stream is empty."
197 [s isAtEnd] whileFalse: [block applyWith: s next].
201 s@(ReadStream traits) do: block separatedBy: sepBlock
202 "Run the separator block between applying the block to each element."
206 ifFalse: [block applyWith: s next].
207 [s isAtEnd] whileFalse:
208 [sepBlock do. block applyWith: s next].
212 s1@(ReadStream traits) with: s2 do: block
213 "Call the block on all the elements in turn until the Stream is empty."
215 [s1 isAtEnd \/ [s2 isAtEnd]] whileFalse:
216 [block applyWith: s1 next with: s2 next].
220 s@(ReadStream traits) detect: succeed ifNone: fail
221 "Find an element satisfying a test. Conditionally execute a failure block."
223 s do: [| :element | (succeed applyWith: element) ifTrue: [^ element]].
227 s@(ReadStream traits) detect: succeed
229 s detect: succeed ifNone: []
232 s@(ReadStream traits) anySatisfy: predicate
233 "Answer whether any elements cause the input block to be True."
235 s do: [| :element | (predicate applyWith: element) ifTrue: [^ True]].
239 s@(ReadStream traits) allSatisfy: predicate
240 "Answer whether all elements cause the input block to be True."
242 s do: [| :element | (predicate applyWith: element) ifFalse: [^ False]].
246 s@(ReadStream traits) noneSatisfy: predicate
247 "Answer whether none of s's elements cause the input block to be True."
249 s do: [| :element | (predicate applyWith: element) ifTrue: [^ False]].
253 streams define: #WriteStream &parents: {Stream}.
254 "Streams that write to some target."
256 s@(WriteStream traits) writer
257 "A WriteStream is already its own resource."
260 s@(WriteStream traits) next: n putInteger: val &littleEndian: le
263 [(le `defaultsTo: Platform Current endianness == #LittleEndian)
264 ifTrue: [0 below: n do:
265 [| :byteIndex | s nextPut: ((val endianByteAt: byteIndex) as: s elementType)]]
266 ifFalse: [n - 1 downTo: 0 do:
267 [| :byteIndex | s nextPut: ((val endianByteAt: byteIndex) as: s elementType)]]].
271 s@(WriteStream traits) next: n putAll: seq startingAt: start
274 s@(WriteStream traits) nextPutAll: c
275 "Place the Collection's contents into the stream."
277 s next: c size putAll: c startingAt: 0
280 s@(WriteStream traits) next: n put: obj
281 "Make the next N values the argument object."
283 buffer ::= s collectionType newSize: n.
284 buffer atAllPut: obj.
288 s@(WriteStream traits) nextPutAll: seq from: start to: end
289 "Place a range of the Sequence's contents into the Stream."
291 s next: end - start putAll: seq from: start
294 s@(WriteStream traits) next: n putAll: seq
296 s next: n putAll: seq startingAt: 0
299 s@(WriteStream traits) nextPut: obj
300 "Place the given element on the Stream."
302 buffer ::= s collectionType newSize: 1.
303 buffer at: 0 put: obj.
304 s next: 1 putAll: buffer startingAt: 0
307 s@(WriteStream traits) ; c
308 "Syntactic sugaring to make collection-insertion similar to concatenation."
314 source@(Stream traits) >> sink@(WriteStream traits)
315 "Write the contents from source to target one element at a time.
316 The source can signal exhausted after an #isAtEnd returns true if
317 it doesn't have anything else left to write."
319 [[source isAtEnd] whileFalse:
320 [sink nextPut: source next]] on: Stream Exhaustion do: [|:c| ^ sink].
324 source@(Stream traits) >> sink
325 [source >> sink writer].
327 sink@(Stream traits) << source
330 x@(Root traits) isSource
331 [#reader isFoundOn: {x}].
333 x@(Root traits) isSink
334 [#writer isFoundOn: {x}].
336 x@(Root traits) isTerminal
337 [x isSource \/ [x isSink]].
339 source@(Root traits) >> sink
340 [source isSource /\ [sink isSink] ifTrue: [source reader >> sink writer]].
342 sink@(Root traits) << source
343 [source isSource /\ [sink isSink] ifTrue: [source reader >> sink writer]].
345 source@(Stream traits) >>; sink
346 "Write the contents from source to target by taking each element as a
347 collection and concatenating their elements."
350 whileFalse: [sink ; source next].
354 sink@(Stream traits) <<; source
357 source@(ReadStream traits) copyTo: sink &chunkSize: n
358 "Write the contents from source to target in big blocks."
361 buffer ::= source collectionType new &capacity: n.
363 [source isAtEnd] whileFalse:
364 [position := [source next: n putInto: buffer]
365 on: source Exhaustion do: #return `er.
367 sink next: position putAll: buffer].
371 streams define: #ReadWriteStream
372 &parents: {ReadStream. WriteStream}.
374 s@(ReadWriteStream traits) iterator
375 "A ReadWriteStream is already its own resource."
378 streams define: #PeekableStream &parents: {Stream}.
379 "A mixin supporting protocols which rely on peek alone, but not full
382 s@(PeekableStream traits) peek
385 s@(PeekableStream traits) nextWhile: testBlock
386 "Answer the next elements for which the test block is True. Note that this
387 relies on a Collection iterator Stream."
390 [s isAtEnd not /\ [testBlock applyWith: s peek]]
391 whileTrue: [result nextPut: s next]] writingAs: s collectionType
394 s@(PeekableStream traits) nextUntil: testBlock
395 "Answer the next elements for which the test block is not True."
397 s nextWhile: [| :each | (testBlock applyWith: each) not]
400 s@(PeekableStream traits) nextDelimitedBy: separatorBlock
401 "Answer the next elements between segments where the separator test is True."
403 s skipWhile: separatorBlock.
404 s nextUntil: separatorBlock
407 s@(PeekableStream traits) skipUntil: condition
408 "Move the position forward until the condition is satisfied."
410 [s isAtEnd \/ [condition apply*, s peek]] whileFalse: [s next]
413 s@(PeekableStream traits) skipWhile: condition
414 "Move the position forward until the condition is no longer satisfied."
416 [s isAtEnd \/ [(condition apply*, s peek) not]] whileFalse: [s next]
419 s@(PeekableStream traits) skipTo: obj
420 "Move the position forward until the object is found. This returns whether
421 it was found or the end was reached before then."
423 s skipUntil: #(= obj) `er
426 streams define: #PositionableStream &parents: {PeekableStream}
427 &slots: {#position -> 0. #readLimit -> 0}.
428 "PositionableStreams have an index and iterate over some sequenced collection,
429 but with a specific limit on the stream."
431 s@(PositionableStream traits) newOn: c from: start to: end
433 s clone `>> [on: c. position := start. readLimit := end. ]
436 s@(PositionableStream traits) on: _
439 s@(PositionableStream traits) contents
440 "Answer the contents of the target up to the readLimit."
443 s@(PositionableStream traits) collectionType
444 "Answer the default collection prototype to dump contents into."
447 s@(PositionableStream traits) last
450 s@(PositionableStream traits) nextMatchAll: c
451 "Whether the next N objects in the Stream are in the other collection
452 (which generally should be a Sequence, ie have linear order)."
456 s next = each ifFalse: [s position := pos. ^ False]].
460 s@(PositionableStream traits) peek
461 "Returns the results of next without advancing the stream."
469 s@(PositionableStream traits) peek: n
470 "Answer the next N results without advancing the stream."
472 origPosition ::= s position.
473 result ::= s next: n.
474 s position := origPosition.
478 s@(PositionableStream traits) peekFor: obj
479 "Returns whether the object is next in the stream. Advances if true."
483 \/ [s position := s position - 1. False]]
486 s@(PositionableStream traits) peekForwardBy: offset
487 "Answers the element the given number of positions after the current position."
490 s@(PositionableStream traits) peekBackBy: offset
491 "Answers the element the given number of positions before the current
493 [s peekForwardBy: offset negated].
495 s@(PositionableStream traits) firstPositionOfAnyOf: targets
496 "Answer the position of the Stream past the next occurrence of the targets,
497 or (one past) the end of the Stream if nothing was found."
499 start ::= s position.
500 [s isAtEnd not /\ [(targets includes: s next) not]] whileTrue.
501 firstMatch := s position.
502 s isAtEnd /\ [s position := s position - 1. (targets includes: s next) not]
503 ifTrue: [firstMatch += 1].
508 s@(PositionableStream traits) upToAnyOf: c
509 "Answer all objects up to the first occurrence of something in the collection,
510 or up to the end of the Stream if they are not found."
512 endMatch ::= s firstPositionOfAnyOf: c.
513 result ::= s next: endMatch - s position - 1.
514 s position := endMatch.
518 s@(PositionableStream traits) upToAll: pattern@(Sequence traits)
519 "Answer all the elements up to the occurrence of the pattern in the Stream,
520 but not including anything from the pattern."
522 patternSize ::= pattern size.
523 start ::= s position.
524 [s readLimit - s position < patternSize] "Not enough room left to match."
526 [(s peek: patternSize) = pattern
527 "The pattern has been found. Answer up to the pattern."
528 ifTrue: [end := s position.
530 ^ (s next: end - start)]
531 "Increment the position past the last start."
532 ifFalse: [s position += 1]].
537 s@(PositionableStream traits) upToEnd
538 "Answer all the elements up to the limit by a copy."
541 s@(PositionableStream traits) through: obj
542 "Answer the next elements up to and including the object given."
543 "This default implementation should be overridden for efficiency."
544 [(s upTo: obj) copyWith: obj].
546 s@(PositionableStream traits) throughAll: pattern
548 result ::= (s collectionType new &capacity: 40) writer.
549 result ; (s upToAll: pattern).
551 ifFalse: [result ; (s next: pattern size)].
555 s@(PositionableStream traits) hasAnEnd [s readLimit < PositiveInfinity].
557 s@(PositionableStream traits) isAtEnd
559 s position >= s readLimit
562 s@(PositionableStream traits) reset
568 s@(PositionableStream traits) resetContents
575 s@(PositionableStream traits) setToEnd
576 "Position the Stream after the last readable element."
578 s position := s readLimit.
582 s@(PositionableStream traits) skip: n
584 s position := s position + n.
588 s@(PositionableStream traits) setFrom: start to: end
591 s readLimit := end + 1.
595 s@(PositionableStream traits) beginsWith: seq
596 "Answer whether the Stream's next elements match the Sequence."
598 s size >= seq size /\
599 [oldPosition ::= s position.
600 starters ::= s next: seq size.
601 s position := oldPosition.
605 s@(PositionableStream traits) retract: n
606 "Retract N elements."
610 s readLimit := s readLimit - n.
614 s@(PositionableStream traits) retract
615 "Retract one element."
618 s@(PositionableStream traits) restoringPositionDo: block
621 block ensure: [s position := pos].
624 streams define: #PositionableReadStream
625 &parents: {PositionableStream. ReadStream}.
626 streams define: #PositionableWriteStream
627 &parents: {PositionableStream. WriteStream}.
628 streams define: #PositionableReadWriteStream
629 &parents: {PositionableStream. ReadStream. WriteStream}.
631 streams define: #StreamProcessor &parents: {ReadStream}
632 &slots: {#source -> Stream clone}.
634 s@(StreamProcessor traits) on: source
636 s source := source reader.
640 s@(StreamProcessor traits) terminal [s source terminal].
642 s@(StreamProcessor traits) collectionType [s source collectionType].
644 s@(StreamProcessor traits) hasAnEnd [s source hasAnEnd].
645 s@(StreamProcessor traits) isAtEnd [s source isAtEnd].
647 source@(ReadStream traits) >> sink@(StreamProcessor traits)
648 "Overrides the basic >> method so that StreamProcessors can be composed
649 associatively in expressions for simple processing tasks."
650 [sink newOn: source].
652 streams define: #FilterStream &parents: {StreamProcessor} &slots: {
653 #block -> [| :_ | True]
655 "FilterStreams take source streams and apply a test block to each element,
656 only returning or acting on elements that satisfy the test."
657 "TODO: make a Write- variant"
658 "The result of sending #next is pre-computed, to determine isAtEnd while
659 not relying on the source stream being repositionable."
661 s@(Stream traits) select: block
662 [(FilterStream newOn: s) `>> [block := block. ]].
664 s@(Stream traits) reject: block
665 [(FilterStream newOn: s) `>> [block := [| :x | (block applyWith: x) not]. ]].
667 s@(FilterStream traits) next: n putInto: seq startingAt: start
670 result ::= seq writer.
671 result position := start.
672 [s source isAtEnd \/ [numWritten >= seq size]] whileFalse:
673 [s source skipUntil: [| :elem | s block applyWith: elem].
674 [s source isAtEnd not /\ [numWritten < seq size /\ [s block applyWith: s source peek]]]
675 whileTrue: [result nextPut: s source next. numWritten += 1]].
679 streams define: #CollectStream &parents: {StreamProcessor} &slots: {
680 #block -> Method Identity "The default action, which is an identity."
682 "CollectStreams take source streams and apply a block to each element,
683 returning the block's result for each."
685 s@(CollectStream traits) collectionType [Array].
687 s@(ReadStream traits) collect: block
688 [(CollectStream newOn: s) `>> [block := block. ]].
690 s@(CollectStream traits) numAvailable [s source numAvailable].
692 s@(CollectStream traits) next: n putInto: seq startingAt: start
694 buffer ::= s source collectionType newSize: n.
695 numRead ::= s source next: n putInto: buffer startingAt: 0.
697 [| :index | seq at: index + start put: (s block apply*, (buffer at: index))].
701 s@(ReadStream traits) project: block
702 [s collect: [| :each | each -> (block applyWith: each)]].
704 streams define: #InjectStream &parents: {StreamProcessor}
705 &slots: {#accumulator -> [| :x :_ | x]. #currentValue -> Nil.}.
707 s@(Stream traits) inject: init into: accumulator
708 [(InjectStream newOn: s) `>> [currentValue: init. accumulator: accumulator. ]].
710 s@(InjectStream traits) next: n putInto: seq startingAt: start
712 buffer ::= s collectionType newSize: n.
713 numRead ::= s source next: n putInto: buffer startingAt: 0.
716 buffer at: index put:
717 (s currentValue := s accumulator apply*, s currentValue, (buffer at: index))].
718 seq replaceFrom: start below: start + numRead with: buffer.
722 s@(InjectStream traits) last
724 [s isAtEnd] whileFalse: [result := s next].
728 source@(ReadStream traits) >> sink@(Method traits)
729 "Overrides the basic >> method so that >> can be composed associatively
730 in expressions for simple processing tasks."
731 [source collect: sink].
733 Stream traits define: #WrapperStream &parents: {ReadWriteStream} &slots: {#original -> Stream clone}.
734 "A WrapperStream wraps some stream and forwards operations to it where
735 applicable. This is an abstraction to be specialized."
736 "The stream to be wrapped."
738 w@(Stream WrapperStream traits) on: s
744 source@(ReadStream traits) >> sink@(Stream WrapperStream traits)
745 [sink newOn: source].
747 w@(Stream WrapperStream traits) terminal [w original terminal].
748 w@(Stream WrapperStream traits) hasAnEnd [w original hasAnEnd].
749 w@(Stream WrapperStream traits) isAtEnd [w original isAtEnd].
750 w@(Stream WrapperStream traits) next [w original next].
751 w@(Stream WrapperStream traits) next: n [w original next: n].
752 w@(Stream WrapperStream traits) next: n putInto: c [w original next: n putInto: c].
753 w@(Stream WrapperStream traits) next: n putInto: c startingAt: start [w original next: n putInto: c startingAt: start].
754 w@(Stream WrapperStream traits) next: n [w original next: n].
755 w@(Stream WrapperStream traits) nextPut: obj [w original nextPut: obj].
756 w@(Stream WrapperStream traits) nextPutAll: seq [w original nextPutAll: seq].
757 w@(Stream WrapperStream traits) next: n putAll: seq [w original next: n putAll: seq].
758 w@(Stream WrapperStream traits) next: n putAll: seq startingAt: start [w original next: n putAll: seq startingAt: start].
759 w@(Stream WrapperStream traits) resource [w original resource].
760 w@(Stream WrapperStream traits) resource: r [w original resource: r].
761 w@(Stream WrapperStream traits) flush [w original flush].
762 w@(Stream WrapperStream traits) position [w original position].
763 w@(Stream WrapperStream traits) position: n [w original position: n].
764 w@(Stream WrapperStream traits) contents [w original contents].
765 w@(Stream WrapperStream traits) elementType [w original elementType].
766 w@(Stream WrapperStream traits) collectionType [w original collectionType].
768 "This is a wrapper mixin for streams that calculates line numbers."
769 streams define: #LineNumberedReadStreamMixin &parents: {Mixin} &slots: {
770 #eolPositions -> ExtensibleArray new. "The positions of the end of each line."
772 "The position of the last character that EOL has been calculated for; we know
773 the line number for all characters before this position and nothing about
775 #previousWasCR -> False.
776 "Whether the previous character was a CR, for CR-LF streams. CR-LF in
777 combination should only increment the line number by 1."
780 s@(LineNumberedReadStreamMixin traits) on: r@(ReadStream traits)
783 s `>> [eolPositions: ({r position} as: ExtensibleArray).
784 lastPosition: r position. previousWasCR: False. ]
787 s@(LineNumberedReadStreamMixin traits) newOn: s2@(LineNumberedReadStreamMixin traits)
788 "LineNumberedStreams should not wrap other ones of the same type."
793 s@(LineNumberedReadStreamMixin traits) lineNumber
794 [| index start stop |
795 (pos ::= s position) >= s eolPositions last
796 ifTrue: [^ s eolPositions size].
798 stop := s eolPositions size.
800 whileTrue: [index := start + stop // 2.
801 (s eolPositions at: index) <= pos
802 ifTrue: [start := index]
803 ifFalse: [stop := index]].
807 s@(LineNumberedReadStreamMixin traits) columnNumber
808 "Returns the index difference from the position to the last eolPosition."
810 s position - s eolPositions last
813 s@(LineNumberedReadStreamMixin traits) atBeginningOfLine
818 s@(LineNumberedReadStreamMixin traits) atBOL
819 [s atBeginningOfLine].
821 s@(LineNumberedReadStreamMixin traits) atEndOfLine
823 s position = s eolPositions last
826 s@(LineNumberedReadStreamMixin traits) atEOL
829 s@(LineNumberedReadStreamMixin traits) next
832 s position - 1 == s lastPosition
833 ifTrue: [s lastPosition: s lastPosition + 1.
834 char = String Character cr
835 ifTrue: [s eolPositions add: s position.
836 s previousWasCR: True]
837 ifFalse: [s previousWasCR not /\ [char = String Character lf]
838 ifTrue: [s eolPositions add: s position].
839 s previousWasCR: False]]
840 ifFalse: [error: 'Got out of sync!'].
844 s@(LineNumberedReadStreamMixin traits) nextLine
846 result ::= s collectionType new writer.
849 (eol := s atEndOfLine) ifFalse: [result nextPut: char].
850 eol \/ [s original isAtEnd]] whileFalse.
851 result contents as: String
854 s@(LineNumberedReadStreamMixin traits) position: n
862 [s position < newPosition /\ [s isAtEnd not]]
868 streams define: #LineNumberedReadStream &parents: {LineNumberedReadStreamMixin. Stream WrapperStream}.
870 streams define: #LineNumberedWriteStreamMixin &parents: {Mixin} &slots: {#currentColumn -> 0. #currentLine -> 0}.
871 "This is a wrapper mixin for streams that keeps track of the cursor and
872 the number of lines printed."
874 s@(LineNumberedWriteStreamMixin traits) updateFrom: char
875 "Detect \n's and update internal state"
879 s currentLine: s currentLine + 1.
883 ifTrue: [s currentColumn: s currentColumn + 8]
884 ifFalse: [s currentColumn: s currentColumn + 1]].
887 s@(LineNumberedWriteStreamMixin traits) padUntilColumn: col with: obj
888 "Detect \n's and update internal state in sync"
890 s next: col - s currentColumn put: obj
893 s@(LineNumberedWriteStreamMixin traits) padUntilColumn: col
894 "Detect \n's and update internal state in sync"
896 s next: col - s currentColumn put: $\s
899 s@(LineNumberedWriteStreamMixin traits) nextPut: char
900 "Detect \n's and update internal state in sync"
906 s@(LineNumberedWriteStreamMixin traits) nextPutAll: seq
907 "Detect \n's and update internal state in sync"
909 seq do: #(s updateFrom: _) `er.