terminals/Xtreams__SequenceableCollectionReadStream.st
changeset 9 6c90659cf105
child 25 02e7c3b6f63c
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/terminals/Xtreams__SequenceableCollectionReadStream.st	Mon Aug 22 16:04:00 2011 +0000
@@ -0,0 +1,159 @@
+"{ Package: 'stx:goodies/xtreams/terminals' }"
+
+"{ NameSpace: Xtreams }"
+
+ReadStream subclass:#SequenceableCollectionReadStream
+	instanceVariableNames:'position'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'My Classes'
+!
+
+SequenceableCollectionReadStream comment:'Read stream on a sequenceable collection.
+{{{
+	(1 to: 10000) reading ++ 1000; read: 5
+}}}
+
+Instance Variables
+	position	<Integer> current position of the stream
+
+'
+!
+
+
+!SequenceableCollectionReadStream methodsFor:'accessing'!
+
+get
+	position = source size ifTrue: [Incomplete zero raise].
+	position := position + 1.
+	^source at: position
+!
+
+read: anInteger into: aSequenceableCollection at: startIndex
+	| count |
+	count := anInteger min: self available.
+	aSequenceableCollection replaceFrom: startIndex to: startIndex + count - 1 with: source startingAt: position + 1.
+	position := position + count.
+	count < anInteger ifTrue: [(Incomplete on: aSequenceableCollection count: count at: startIndex) raise].
+	^anInteger
+! !
+
+!SequenceableCollectionReadStream methodsFor:'initialize-release'!
+
+close
+!
+
+contentsSpecies
+	^source species
+!
+
+on: aSequenceableCollection
+	super on: aSequenceableCollection.
+	position := 0
+! !
+
+!SequenceableCollectionReadStream methodsFor:'printing'!
+
+streamingPrintOn: aStream
+	| tail head |
+	super streamingPrintOn: aStream.
+	tail := position min: 5.
+	head := (source size - position) min: (10 - tail).
+	aStream
+		write: ' position: ';
+		print: position;
+		write: ' size: ';
+		print: source size;
+		cr; tab;
+		write: (position > 5 ifTrue: ['...'] ifFalse: ['']);
+		print: (source copyFrom: position + 1 - tail to: position);
+		write: '  |  ';
+		print: (source copyFrom: position + 1 to: position + head);
+		write: (source size - position > (10 - tail) ifTrue: ['...'] ifFalse: [''])
+! !
+
+!SequenceableCollectionReadStream methodsFor:'private'!
+
+streamingInsert: anInteger into: aWriteStream
+	| count |
+	anInteger isZero ifTrue: [^self].
+	count := anInteger min: self available.
+	aWriteStream insert: count from: source at: position + 1.
+	position := position + count.
+	count >= anInteger ifTrue: [^self].
+	(Incomplete on: source count: count at: position - count + 1) raise
+!
+
+streamingInsertInto: aWriteStream
+	| count |
+	(count := self available) isZero ifTrue: [Incomplete zero raise].
+	self streamingInsert: count into: aWriteStream.
+	^count
+!
+
+streamingWrite: anInteger into: aWriteStream
+	| count |
+	anInteger isZero ifTrue: [^0].
+	count := anInteger min: self available.
+	aWriteStream write: count from: source at: position + 1.
+	position := position + count.
+	count = anInteger ifTrue: [^anInteger].
+	(Incomplete on: source count: count at: position - count + 1) raise
+!
+
+streamingWriteInto: aWriteStream
+	| count |
+	(count := self available) isZero ifTrue: [^self].
+	self streamingWrite: count into: aWriteStream.
+	^count
+! !
+
+!SequenceableCollectionReadStream methodsFor:'seeking'!
+
+++ anInteger
+	| count |
+	anInteger < 0 ifTrue: [ ^self -- anInteger negated ].
+	count := self available min: anInteger.
+	position := position + count.
+	count < anInteger ifTrue: [(Incomplete count: count) raise].
+	^anInteger
+!
+
+-- anInteger
+	| count |
+	anInteger < 0 ifTrue: [ ^self ++ anInteger negated ].
+	count := position min: anInteger.
+	position := position - count.
+	count = anInteger ifTrue: [^anInteger].
+	(Incomplete count: count) raise
+!
+
+length
+	^source size
+!
+
+position
+	" Return a bookmark for the current stream state. "
+
+	^position
+!
+
+position: aPosition
+
+	aPosition < 0 ifTrue: [ Incomplete zero raise ].
+	position := aPosition min: self length.
+	position = aPosition ifTrue: [^aPosition ].
+	(Incomplete count: position) raise
+! !
+
+!SequenceableCollectionReadStream methodsFor:'testing'!
+
+isPositionable
+	^true
+! !
+
+!SequenceableCollectionReadStream class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id$'
+! !