terminals/Xtreams__SequenceableCollectionWriteStream.st
author Martin Kobetic
Sun, 17 Nov 2013 00:23:18 -0500
changeset 147 bd6be28aa924
parent 109 9587e2df7029
permissions -rw-r--r--
merging

"{ Package: 'stx:goodies/xtreams/terminals' }"

"{ NameSpace: Xtreams }"

WriteStream subclass:#SequenceableCollectionWriteStream
	instanceVariableNames:'position length'
	classVariableNames:''
	poolDictionaries:'XtreamsPool'
	category:'Xtreams-Terminals'
!

SequenceableCollectionWriteStream comment:'Write stream on a sequenceable collection. The collection is grown automatically to accommodate any elements written. Closing a collection write stream will truncate the collection to the current stream position. This behavior is useful as a replacement for the traditional #contents message. The contents can be accessed with the #terminal message after the stream is closed.
{{{
	String new writing write: ''Hello World''; -- 6; close; terminal
}}}

Instance Variables
	position        <Integer> current position of the stream
	length  <Integer> number of valid elements in the destination

'
!


!SequenceableCollectionWriteStream methodsFor:'accessing'!

contents
	^destination copyFrom: 1 to: position
!

insert: anInteger from: aSequenceableCollection at: startIndex
	destination := destination copyGrownToAtLeast: destination size + anInteger.
	destination replaceFrom: position + anInteger + 1 to: length + anInteger with: destination startingAt: position + 1.
	destination replaceFrom: position + 1 to: position + anInteger with: aSequenceableCollection startingAt: startIndex.
	position := position + anInteger.
	length := length + anInteger.
	^anInteger
!

put: anObject
	| free |
	free := destination size - position.
	free < 1 ifTrue: [destination := destination copyGrownToAtLeast: destination size + 1].
	position := position + 1.
	destination at: position put: anObject.
	length := length + 1.
	^anObject
!

write: anInteger from: aSequenceableCollection at: startIndex
	| available |
	available := destination size - position.
	available < anInteger ifTrue: [destination := destination copyGrownToAtLeast: destination size + anInteger - available].
	destination replaceFrom: position + 1 to: position + anInteger with: aSequenceableCollection startingAt: startIndex.
	position := position + anInteger.
	position > length ifTrue: [length := position].
	^anInteger
! !

!SequenceableCollectionWriteStream methodsFor:'initialize-release'!

close
	destination := destination copyFrom: 1 to: position
!

contentsSpecies
	^destination species
!

flush
!

on: aSequenceableCollection
	super on: aSequenceableCollection.
	position := 0.
	length := 0
! !

!SequenceableCollectionWriteStream methodsFor:'printing'!

streamingPrintOn: aStream
	| tail head |
	super streamingPrintOn: aStream.
	tail := position min: 5.
	head := (destination size - position) min: (10 - tail).
	aStream
		write: ' position: ';
		print: position;
		write: ' size: ';
		print: destination size;
		cr; tab;
		write: (position > 5 ifTrue: ['...'] ifFalse: ['']);
		print: (destination copyFrom: position + 1 - tail to: position);
		write: '  |  ';
		print: (destination copyFrom: position + 1 to: position + head);
		write: (destination size - position > (10 - tail) ifTrue: ['...'] ifFalse: [''])
! !

!SequenceableCollectionWriteStream methodsFor:'private'!

streamingInsert: anInteger from: aStreamable
	| reading |
	reading := aStreamable reading.
	destination := destination copyGrownToAtLeast: destination size + anInteger.
	destination replaceFrom: position + anInteger to: destination size with: destination startingAt: position.
	[reading read: anInteger into: destination at: position + 1]
		on: Incomplete do: [:error | position := position + error count. error pass].
	position := position + anInteger
!

streamingInsertFrom: aStreamable
	self error: 'Not Yet Implemented'
!

streamingWrite: anInteger from: aReadStream
	| available |
	available := destination size - position.
	available < anInteger ifTrue: [destination := destination copyGrownToAtLeast: destination size + anInteger - available].
	[aReadStream read: anInteger into: destination at: position + 1]
		on: Incomplete do: [:error |
			position := position + error count.
			position > length ifTrue: [length := position].
			error pass].
	position := position + anInteger.
	position > length ifTrue: [length := position].
	^anInteger
!

streamingWriteFrom: aReadStream
	| available count chunkSize |
	count := 0.
	chunkSize := DefaultBufferSize.
	^[[available := destination size - position.
	available < chunkSize ifTrue: [destination := destination copyGrownToAtLeast: destination size + chunkSize].
	aReadStream read: chunkSize into: destination at: position + 1.
	position := position + chunkSize.
	count := count + chunkSize] repeat]
		on: Incomplete do: [:exception |
			position := position + exception count.
			position > length ifTrue: [length := position].
			count + exception count]
! !

!SequenceableCollectionWriteStream 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
	^length
!

position
	^position
!

position: aPosition
	aPosition < 0 ifTrue: [ Incomplete zero raise ].
	position := aPosition min: self length.
	position = aPosition ifTrue: [^aPosition].
	(Incomplete count: position) raise
! !

!SequenceableCollectionWriteStream methodsFor:'testing'!

isPositionable
	^true
! !

!SequenceableCollectionWriteStream class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !