substreams/Xtreams__TestWriteSubstream.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 01 Feb 2012 00:56:17 +0000
changeset 103 726bf2ca0b99
parent 67 a87e5ce04545
child 109 9587e2df7029
permissions -rw-r--r--
Removed methods from FileHandle to make it compilable. Having methods there is not a good idea anyway.

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

"{ NameSpace: Xtreams }"

WriteSubstream subclass:#TestWriteSubstream
	instanceVariableNames:'substreamAtEnd test inclusive'
	classVariableNames:''
	poolDictionaries:''
	category:'Xtreams-Substreams'
!

TestWriteSubstream comment:'This is a substream bounded by an element matching the @test criteria.

Instance Variables
	substreamAtEnd	<Boolean> is this substream at end
	test	<BlockClosure> the bounding criteria
	inclusive	<Boolean> is the boundary part of the substream contents

'
!


!TestWriteSubstream class methodsFor:'instance creation'!

on: aDestination test: testBlock inclusive: aBoolean
	^self new on: aDestination test: testBlock inclusive: aBoolean
! !

!TestWriteSubstream methodsFor:'accessing'!

insert: anInteger from: aSequenceableCollection at: startIndex
	^self write: anInteger from: aSequenceableCollection at: startIndex
!

put: anObject
	substreamAtEnd ifTrue: [Incomplete zero raise].
	((substreamAtEnd := test value: anObject) and: [inclusive not]) ifTrue: [Incomplete zero raise].
	[destination put: anObject] on: Incomplete do: [:incomplete | destinationAtEnd := substreamAtEnd := true. incomplete pass].
	^anObject
!

write: anInteger from: aSequenceableCollection at: startIndex
	| count object |
	substreamAtEnd ifTrue: [Incomplete zero raise].
	count := 0.
	[[count < anInteger and: [substreamAtEnd not]] whileTrue:
		[object := aSequenceableCollection at: startIndex + count.
		((substreamAtEnd := test value: object) and: [inclusive not]) ifFalse: [destination put: object].
		count := count + 1]]
			on: Incomplete do: [:incomplete |
				destinationAtEnd := substreamAtEnd := true.
				(Incomplete on: aSequenceableCollection count: count at: startIndex) raise].
	count < anInteger ifTrue: [(Incomplete on: aSequenceableCollection count: count at: startIndex) raise].
	^anInteger
! !

!TestWriteSubstream methodsFor:'initialize-release'!

on: aDestination test: testBlock inclusive: aBoolean
	self on: aDestination.
	test := testBlock.
	inclusive := aBoolean.
	substreamAtEnd := false
! !

!TestWriteSubstream methodsFor:'private'!

streamingInsert: anInteger from: aReadStream
	self streamingWrite: anInteger from: aReadStream
!

streamingInsertFrom: aReadStream
	self streamingWriteFrom: aReadStream
!

streamingWrite: anInteger from: aReadStream
	| count object |
	substreamAtEnd ifTrue: [Incomplete zero raise].
	count := 0.
	[[count < anInteger and: [substreamAtEnd not]] whileTrue:
		[object := aReadStream get.
		((substreamAtEnd := test value: object) and: [inclusive not]) ifFalse: [destination put: object].
		count := count + 1]]
			on: Incomplete do: [:incomplete |
				destinationAtEnd := substreamAtEnd := true.
				(Incomplete count: count) raise].
	count < anInteger ifTrue: [(Incomplete count: count) raise].
	^anInteger
!

streamingWriteFrom: aReadStream
	| object count |
	substreamAtEnd ifTrue: [Incomplete zero raise].
	count := 0.
	^[[substreamAtEnd not] whileTrue:
		[object := aReadStream get.
		((substreamAtEnd := test value: object) and: [inclusive not]) ifFalse: [destination put: object. count := count + 1]].
		count
	] on: Incomplete do: [:incomplete | destinationAtEnd := substreamAtEnd := true. count ]
! !

!TestWriteSubstream methodsFor:'testing'!

isPositionable
	^false
! !

!TestWriteSubstream class methodsFor:'documentation'!

version_SVN
    ^ '$Id$'
! !