substreams/Xtreams__MatchWriteSubstream.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:#MatchWriteSubstream
	instanceVariableNames:'substreamAtEnd pattern patternStart inclusive backtrack'
	classVariableNames:''
	poolDictionaries:''
	category:'Xtreams-Substreams'
!

MatchWriteSubstream comment:'This is a substream bounded by a string pattern. The algorithm used doesn''t need to peek or step back to detect the pattern, so it can be used on non-positionable streams.

Instance Variables
	substreamAtEnd	<Boolean> is this substream at end
	pattern	<String> the bounding pattern
	patternStart	<Integer> 
	inclusive	<Boolean> is the boundary part of the substream contents
	backtrack	<Array> backtracking table for pattern

'
!


!MatchWriteSubstream class methodsFor:'instance creation'!

on: aDestination pattern: aPattern backtrack: aBacktrack inclusive: aBoolean
	^self new on: aDestination pattern: aPattern backtrack: aBacktrack inclusive: aBoolean
! !

!MatchWriteSubstream methodsFor:'accessing'!

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

put: anObject
	substreamAtEnd ifTrue: [Incomplete zero raise].
	[self gobble: anObject] on: Incomplete do: [:incomplete | destinationAtEnd := substreamAtEnd := true. incomplete pass].
	^anObject
!

write: anInteger from: aSequenceableCollection at: startIndex
	| count |
	count := 0.
	[[count < anInteger and: [substreamAtEnd not]] whileTrue:
		[self gobble: (aSequenceableCollection at: startIndex + count).
		count := count + 1]]
			on: Incomplete do: [:incomplete |
				destinationAtEnd := substreamAtEnd := true.
				(Incomplete on: aSequenceableCollection count: count at: startIndex) raise].
	count < anInteger ifTrue:
		[substreamAtEnd := true.
		(Incomplete on: aSequenceableCollection count: count at: startIndex) raise].
	^anInteger
! !

!MatchWriteSubstream methodsFor:'initialize-release'!

on: aDestination pattern: aPattern backtrack: aBacktrack inclusive: aBoolean
	self on: aDestination.
	pattern := aPattern.
	backtrack := aBacktrack.
	patternStart := 1.
	inclusive := aBoolean.
	substreamAtEnd := false
! !

!MatchWriteSubstream methodsFor:'private'!

gobble: anObject
	| patternStop match |
	patternStop := patternStart.
	(match := anObject = (pattern at: patternStop)) ifTrue: [patternStop := patternStop + 1].

	"A full pattern match"
	patternStop > pattern size ifTrue: [
		inclusive ifTrue: [destination write: pattern size from: pattern at: 1].
		substreamAtEnd := true.
		^self].

	"Partial match, in progress"
	match ifTrue: [patternStart := patternStop. ^self].

	"No match at all, write out the object we just read"
	patternStart = 1 ifTrue: [
		destination put: anObject.
		patternStart := 1.
		^self].

	"Partial match was in progress, but anObject didn't match, so write out the part of the pattern and try anObject again from the backtrack position"
	destination write: patternStart - 1 from: pattern at: 1.
	patternStart := backtrack at: patternStop.
	self gobble: anObject
!

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

streamingInsertFrom: aReadStream
	self streamingWriteFrom: aReadStream
!

streamingWrite: anInteger from: aReadStream
	| count |
	count := 0.
	[[count < anInteger and: [substreamAtEnd not]] whileTrue:
		[self gobble: aReadStream get.
		count := count + 1]]
			on: Incomplete do: [:incomplete |
				destinationAtEnd := substreamAtEnd := true.
				(Incomplete count: count) raise].
	count < anInteger ifTrue:
		[substreamAtEnd := true.
		(Incomplete count: count) raise].
	^anInteger
!

streamingWriteFrom: aReadStream
	| count |
	substreamAtEnd ifTrue: [Incomplete zero raise].
	count := 0.
	^[[substreamAtEnd not] whileTrue: [self gobble: aReadStream get. count := count + 1]]
		on: Incomplete do: [:incomplete | destinationAtEnd := substreamAtEnd := true. count ]
! !

!MatchWriteSubstream class methodsFor:'documentation'!

version_SVN
    ^ '$Id$'
! !