PositionableStream.st
author sr
Fri, 27 May 2011 16:22:27 +0200
changeset 13379 a4644dee3177
parent 11434 525e70af011a
child 14934 5e273cddded7
child 18011 deb0c3355881
permissions -rw-r--r--
changed: #on: check for collection passed

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic' }"

PeekableStream subclass:#PositionableStream
	instanceVariableNames:'collection position readLimit writeLimit'
	classVariableNames:'ZeroPosition InvalidPositionErrorSignal'
	poolDictionaries:''
	category:'Streams'
!

!PositionableStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    Instances of PositionableStream allow positioning the read pointer.
    The PositionableStream class also adds methods for source-chunk reading
    and writing, and for filing-in/out of source code.

    This is an abstract class.

    Compatibility Notice:
        In previous versions of ST/X, streams started with a 1-position (i.e. as in collections),
        while ST-80 has always been using 0-based postions for streams and 1-based positions for collections.

    THIS CERTAINLY IS BAD.

    Although this is confusing ST/X has been changed to now also use 0-based stream positioning.

    [author:]
        Claus Gittinger
"
! !

!PositionableStream class methodsFor:'initialization'!

initialize
    ZeroPosition := 0.        "/ changed with stx rel5.1

    InvalidPositionErrorSignal isNil ifTrue:[
        InvalidPositionErrorSignal := PositionOutOfBoundsError.
        InvalidPositionErrorSignal notifierString:'position out of bounds: '.
    ]
! !

!PositionableStream class methodsFor:'instance creation'!

on:aCollection
    "return a new PositionableStream streaming on aCollection"

    ^ (self basicNew) on:aCollection
!

on:aCollection from:first to:last
    "return a new PositionableStream streaming on aCollection
     from first to last"

    ^ (self basicNew) on:aCollection from:first to:last
!

with:aCollection
    "return a new PositionableStream streaming on aCollection,
     the stream is positioned to the end of the collection."

    ^ (self basicNew) with:aCollection
! !

!PositionableStream class methodsFor:'Signal constants'!

invalidPositionErrorSignal
    "return the signal raised if positioning is attempted to an
     invalid position (i.e. before the begin of the stream or after
     the end)"

    ^ PositionOutOfBoundsError
! !

!PositionableStream class methodsFor:'constants'!

zeroPosition
    "return the number, which marks the initial position.
     Compatibility Notice:
        In previous versions of ST/X, streams started with a 1-position (i.e. as in collections),
        while ST-80 has always been using 0-based postions for streams and 1-based positions for collections.

     Although this is confusing ST/X has been changed to now also use 0-based stream positioning.
    "

    ^ ZeroPosition

    "Modified: / 13-07-2006 / 20:36:54 / cg"
! !

!PositionableStream methodsFor:'Compatibility-Dolphin'!

endChunk
    self nextPutChunkSeparator
! !

!PositionableStream methodsFor:'Compatibility-ST/V'!

skipTo:anElement
    "ST/V compatibility:
     skip for the element given by the argument, anElement;
     return nil if not found, self otherwise. 
     On a successful match, the next read will return the element after anElement."

    ^ self skipThrough:anElement

    "
     |s|
     s := ReadStream on:'12345678901234567890'.
     s skipTo:$5.
     s copyFrom:1 to:(s position).    
     s upToEnd      
    "
! !

!PositionableStream methodsFor:'accessing'!

collection
    ^ collection
!

contents
    "return the entire contents of the stream"

    ^ collection
!

peek
    "look ahead for and return the next element"

    |peekObject|

    peekObject := self next.
    self backStep.
    ^ peekObject
!

peekForAll:aCollection
    "return true and advance if the next elements are the same
     as aCollection. 
     otherwise stay and let the position unchanged"

    |oldPos|

    oldPos := self position.
    (self next:(aCollection size)) = aCollection ifTrue:[
	^ true
    ].
    self position:oldPos.
    ^ false

    "Created: 1.3.1997 / 15:11:25 / cg"
!

readLimit
    "return the read-limit; thats the position at which EOF is returned"

    ^ readLimit

    "Created: / 30.10.1998 / 16:47:04 / cg"
!

readLimit:aNumber
    "set the read-limit; thats the position at which EOF is returned"

    readLimit := aNumber
!

writeLimit:aNumber
    "set the writeLimit; thats the position after which writing is prohibited"

    writeLimit := aNumber

    "
     |s|
     s := WriteStream on:String new.
     s nextPutAll:'hello world'.
     s contents.

     |s|
     s := WriteStream on:String new.
     s writeLimit:5.
     s nextPutAll:'hello world'.
     s contents.

    "

    "Modified: / 04-06-2007 / 17:21:55 / cg"
! !

!PositionableStream methodsFor:'positioning'!

backStep
    "move backward read position by one"

    self position:(self position - 1)
!

position
    "return the read position"

    ZeroPosition == 0 ifTrue:[
        ^ self position0Based
    ] ifFalse:[
        ^ self position1Based
    ].
!

position0Based
    "return the read position 0-based"

    ^ position - ZeroPosition
!

position0Based:index0Based
    "set the read (or write) position"

    ((index0Based > readLimit) or:[index0Based < 0]) ifTrue: [^ self positionError:index0Based].
    position := index0Based + ZeroPosition
!

position1Based
    "return the read position 1-based"

    ^ self position0Based + 1
!

position1Based:index1Based
    "set the read (or write) position"

    self position0Based:(index1Based - 1)

    "
     |s|

     s := '1234567890' readStream.
     s next:5.
     s position:1.
     s next:7.       
    "

    "
     |s|

     s := '' writeStream.
     s nextPutAll:'1234567890'.
     s position:5.
     s nextPutAll:'abcdefg'.
     s contents 
    "

    "
     |s|

     s := '' writeStream.
     s nextPutAll:'1234567890'.
     s position:0.
     s nextPutAll:'abcdefg'.
     s contents 
    "
!

position:newPos
    "set the read (or write) position"

    ZeroPosition == 0 ifTrue:[
        ^ self position0Based:newPos
    ] ifFalse:[
        ^ self position1Based:newPos
    ].

    "
     |s|

     s := '1234567890' readStream.
     s next:5.
     s position:1.
     s next:7.       
    "

    "
     |s|

     s := '' writeStream.
     s nextPutAll:'1234567890'.
     s position:5.
     s nextPutAll:'abcdefg'.
     s contents 
    "

    "
     |s|

     s := '' writeStream.
     s nextPutAll:'1234567890'.
     s position:0.
     s nextPutAll:'abcdefg'.
     s contents 
    "
!

reset
    "set the read position to the beginning of the collection"

    self resetPosition

    "
     |s|

     s := 'hello world' readStream.
     Transcript showCR:(s next:5).
     s reset.
     Transcript showCR:(s next:10).
    "
!

resetPosition
    "set the read position to the beginning of the collection"

    position := ZeroPosition

    "
     |s|

     s := 'hello world' readStream.
     Transcript showCR:(s next:5).
     s reset.
     Transcript showCR:(s next:10).
    "
!

setToEnd
    "set the read position to the end of the collection.
     #next will return EOF, #nextPut: will append to the stream.
     (same Behavior as FileStream."

    position := readLimit + ZeroPosition
!

skip:numberToSkip
    "skip the next numberToSkip elements"

    numberToSkip ~~ 0 ifTrue:[
	self position:(self position + numberToSkip)
    ]
!

skipThroughAll:aCollection
    "skip for and through the sequence given by the argument, aCollection;
     return nil if not found, self otherwise. 
     On a successful match, the next read will return elements after aCollection;
     if no match was found, the receiver will be positioned at the end.
     This is redefined here, to make use of positioning."

    |buffer len first idx|

    len := aCollection size.
    first := aCollection at:1.
    [self atEnd] whileFalse:[
        buffer := self nextAvailable:len.
        buffer = aCollection ifTrue:[
            ^ self
        ].
        buffer size == len ifTrue:[
            "expect more input"
            idx := buffer indexOf:first startingAt:2.
            idx == 0 ifFalse:[
                self position:(self position - len + idx - 1)
            ].
        ].
    ].
    ^ nil

    "
     |s|
     s := ReadStream on:'12345678901234567890a'.
     s skipThroughAll:'90ab'.
     s upToEnd  
    "
    "
     |s|
     s := ReadStream on:'12345678901234567890'.
     s skipThroughAll:'1234'.
     s upToEnd  
    "
    "
     |s|
     s := ReadStream on:'12345678901234567890'.
     s skipThroughAll:'999'.
     s atEnd  
    "

    "Created: 26.6.1996 / 09:35:35 / cg"
    "Modified: 11.1.1997 / 19:16:38 / cg"
!

skipToAll:aCollection
    "skip for the sequence given by the argument, aCollection;
     return nil if not found, self otherwise. 
     On a successful match, the next read will return elements of aCollection."

    |oldPos buffer len first idx|

    oldPos := self position.
    len := aCollection size.
    first := aCollection at:1.
    [self atEnd] whileFalse:[
        buffer := self nextAvailable:len.
        buffer = aCollection ifTrue:[
            self position:(self position - len).
            ^ self
        ].
        buffer size == len ifTrue:[
            "more input can be expected"
            idx := buffer indexOf:first startingAt:2.
            idx == 0 ifFalse:[
                self position:(self position - len + idx - 1)
            ].
        ].
    ].
    self position:oldPos.
    ^ nil

    "
     |s|
     s := ReadStream on:'12345678901234567890'.
     s skipToAll:'901'.
     s upToEnd  
    "

    "
     |s|
     s := ReadStream on:'1234567890'.
     s skipToAll:'901'.
     s upToEnd  
    "

    "
     |s|
     s := 'Makefile' asFilename readStream.
     [
         (s skipToAll:'EDIT') notNil ifTrue:[
            s next:100.
         ].
     ] ensure:[
        s close.
     ]
    "

    "Modified: 26.6.1996 / 09:28:27 / cg"
    "Created: 26.6.1996 / 09:35:06 / cg"
! !

!PositionableStream methodsFor:'printing & storing'!

printOn:aStream
    aStream nextPutAll:self className; nextPutAll:'(on:'; nextPutAll:collection classNameWithArticle; nextPut:$)

    "
      '' readStream printString
      '' writeStream printString
    "
! !

!PositionableStream methodsFor:'private'!

contentsSpecies
    "return a class of which instances will be returned, when
     parts of the collection are asked for. 
     (see upTo-kind of methods in subclasses)"

    ^ collection species
!

on:aCollection
    "setup for streaming on aCollection"

    collection := aCollection.
    readLimit := aCollection size.
    readLimit == 0 ifTrue:[
        self assert:(aCollection isCollection)
    ].
    position := ZeroPosition
!

on:aCollection from:first to:last
    "setup for streaming on aCollection from first to last"

    collection := aCollection.
    position := first - 1 + ZeroPosition.
    readLimit := last
!

positionError
    "{ Pragma: +optSpace }"

    "report an error when positioning past the end
     or before the beginning."

    ^ PositionOutOfBoundsError raiseRequestWith:nil

    "Modified: / 26.7.1999 / 10:59:13 / stefan"
!

positionError:badPostition
    "{ Pragma: +optSpace }"

    "report an error when positioning past the end
     or before the beginning."

    ^ PositionOutOfBoundsError raiseRequestWith:badPostition
!

with:aCollection
    "setup for streaming to the end of aCollection"

    collection := aCollection.
    readLimit := aCollection size.
    self setToEnd

    "
      (WriteStream with:#(1 2 3 4 5)) 
            nextPut:6;
            contents
    "
! !

!PositionableStream methodsFor:'reading'!

nextAvailable:count
    |end result|

    end := position + count.
    (end - ZeroPosition + 1) > readLimit ifTrue:[
        end := readLimit.
    ].

    result := collection copyFrom:position+1-ZeroPosition to:end.
    position := end.
    ^ result.

    "
        'abc' readStream nextAvailable:1.
        'abc' readStream nextAvailable:2.
        'abc' readStream nextAvailable:3.
        'abc' readStream nextAvailable:4.

        'abc' readStream nextAvailable:2; nextAvailable:2.
        'abc' readStream nextAvailable:3; nextAvailable:3.
    "
!

upToAll:aCollection
    "read until a subcollection consisisting of the elements in aCollection
     is encountered.
     Return everything read excluding the elements in aCollection.
     The position is left before the collection; i.e. the next
     read operations will return those elements.
     If no such subcollection is encountered, all elements up to the end 
     are read and returned.
     See also #throughAll: which also reads up to some objects
     but positions behind it and DOES include it in the returned
     collection.
     See also #upToAllExcluding:, which returns the same, but leaves the
     read pointer after the matched subcollection.

     Note: this behavior is inconsistent with the other upTo.. methods,
	   which position after the found item. We implement the method
	   this way for the sake of ST80-compatibility."

    |answerStream element last rslt|

    last := aCollection last.
    answerStream := WriteStream on:(self contentsSpecies new).
    [self atEnd] whileFalse:[
	element := self next.
	answerStream nextPut:element.
	element == last ifTrue:[
	    ((rslt := answerStream contents) endsWith:aCollection) ifTrue:[
		self position:(self position - aCollection size).
		^ rslt copyWithoutLast:aCollection size
	    ]
	].
    ].
    ^ answerStream contents

    "
     |s|
     s := ReadStream on:'hello world'.
     Transcript show:'<'; show:(s upToAll:'wo'); showCR:'>'. 
     Transcript showCR:s atEnd.
     Transcript show:'<'; show:(s upToEnd); showCR:'>'. 
    "
    "
     |s|
     s := ReadStream on:'hello world'.
     Transcript show:'<'; show:(s upToAll:'xx'); showCR:'>'. 
     Transcript showCR:s atEnd.
     Transcript show:'<'; show:(s upToEnd); showCR:'>'. 
    "

    "Modified: / 12.1.1998 / 22:06:42 / cg"
    "Created: / 12.1.1998 / 22:07:01 / cg"
! !

!PositionableStream methodsFor:'testing'!

atEnd
    "return true, if the read-position is at the end"

    ^ (position - ZeroPosition + 1) > readLimit
!

isEmpty
    "return true, if the contents of the stream is empty"

    ^ readLimit == 0
!

isInternalByteStream
    "return true, if the stream is an internal stream reading bytes"

    ^ collection class isBytes

    "Created: / 30-05-2007 / 16:16:12 / cg"
!

isPositionable
    "return true, if the stream supports positioning (this one is)"

    ^ true
! !

!PositionableStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/PositionableStream.st,v 1.154 2011-05-27 14:22:27 sr Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/PositionableStream.st,v 1.154 2011-05-27 14:22:27 sr Exp $'
! !

PositionableStream initialize!