substreams/Xtreams__PositionWriteSubstream.st
author joe
Fri, 15 Mar 2013 19:54:41 -0400
changeset 113 c0df9d2ad5d3
parent 109 9587e2df7029
permissions -rw-r--r--
* make InifiniteReadingWritingTests abstract

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

"{ NameSpace: Xtreams }"

WriteSubstream subclass:#PositionWriteSubstream
	instanceVariableNames:'position'
	classVariableNames:''
	poolDictionaries:''
	category:'Xtreams-Substreams'
!

PositionWriteSubstream comment:'This is an abstract substreams that keeps track of its own position and allows positioning if the underlying stream is positionable.

Instance Variables
	position        <Integer> current position within the substream

'
!


!PositionWriteSubstream methodsFor:'accessing'!

insert: anInteger from: aSequenceableCollection at: startIndex
	[destination insert: anInteger from: aSequenceableCollection at: startIndex] on: Incomplete do: [:incomplete |
		position := position + incomplete count.
		incomplete pass].
	position := position + anInteger.
	^anInteger
!

put: anObject
	| object |
	object := destination put: anObject.
	position := position + 1.
	^object
!

write: anInteger from: aSequenceableCollection at: startIndex
	[destination write: anInteger from: aSequenceableCollection at: startIndex] on: Incomplete do: [:incomplete |
		position := position + incomplete count.
		incomplete pass].
	position := position + anInteger.
	^anInteger
! !

!PositionWriteSubstream methodsFor:'initialize-release'!

on: aDestination
	super on: aDestination.
	position := 0
! !

!PositionWriteSubstream methodsFor:'seeking'!

++ anInteger
	| count |
	anInteger < 0 ifTrue: [ ^self -- anInteger negated ].
	count := self available min: anInteger.
	count := [destination ++ count. count] on: Incomplete do: [ :ex | ex count ].
	position := position + count.
	count < anInteger ifTrue: [destinationAtEnd := true. (Incomplete count: count) raise].
	^anInteger
!

-- anInteger
	| count |
	anInteger < 0 ifTrue: [ ^self ++ anInteger negated ].
	count := anInteger min: position.
	count := [destination -- count. count] on: Incomplete do: [ :ex | ex count ].
	position := position - count.
	count < anInteger ifTrue: [(Incomplete count: count) raise].
	anInteger isZero ifFalse: [destinationAtEnd := false].
	^anInteger
!

-= anInteger
	position := self length - anInteger max: 0.
	^destination -= anInteger.
!

length
	^destination available + position
!

position
	^position
!

position: anInteger
	| available adjustment |
	self isPositionable ifFalse: [self error: 'This stream is not positionable.'].

	anInteger < 0 ifTrue: [Incomplete zero raise].
	available := anInteger min: self length.
	adjustment := available - position.
	adjustment positive
		ifTrue: [ destination ++ adjustment ]
		ifFalse: [ destination -- adjustment negated ].
	position := available.
	available = anInteger ifTrue: [^anInteger].
	(Incomplete count: available) raise
! !

!PositionWriteSubstream methodsFor:'testing'!

isPositionable
	^destination isPositionable
! !

!PositionWriteSubstream class methodsFor:'documentation'!

version_HG

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