PeekableStream.st
author Claus Gittinger <cg@exept.de>
Fri, 02 Aug 2002 19:27:04 +0200
changeset 6707 790fc577c403
parent 5394 f877659e09f7
child 7685 535a69a7cd69
permissions -rw-r--r--
button labels uppercase

"
 COPYRIGHT (c) 1994 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' }"

Stream subclass:#PeekableStream
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Streams'
!

!PeekableStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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
"
    abstract superclass for all Stream which support read-ahead
    (i.e. peeking) of one element.
    Concrete subclasses must implement a peek method.

    [author:]
        Claus Gittinger
"
! !

!PeekableStream methodsFor:'chunk input/output'!

nextChunk
    "return the next chunk, i.e. all characters up to the next
     exclamation mark. Within the chunk, exclamation marks have to be doubled,
     they are undoubled here.
     Except for primitive code, in which doubling is not needed (allowed).
     This exception was added to make it easier to edit primitive code with 
     external editors. However, this means, that other Smalltalks cannot always 
     read chunks containing primitive code 
     - but that doesnt really matter, since C-primitives are an ST/X feature anyway."

    |theString sep newString done thisChar nextChar inPrimitive
     index    "{ Class:SmallInteger }"
     currSize "{ Class:SmallInteger }" |

    sep := ChunkSeparator.
    theString := String new:500.
    currSize := 500.
    thisChar := self skipSeparators.
    thisChar := self next.
    index := 0.
    done := false.
    inPrimitive := false.

    [done] whileFalse:[
	((index + 2) <= currSize) ifFalse:[
	    newString := String new:(currSize * 2).
	    newString replaceFrom:1 to:currSize with:theString.
	    currSize := currSize * 2.
	    theString := newString
	].
	thisChar isNil ifTrue:[
	    done := true
	] ifFalse:[
	    (thisChar == $% ) ifTrue:[
		nextChar := self peek.
		(nextChar == ${ ) ifTrue:[
		    inPrimitive := true.
		    index := index + 1.
		    theString at:index put:thisChar.
		    thisChar := self next
		] ifFalse:[
		    (nextChar == $} ) ifTrue:[
			inPrimitive := false.
			index := index + 1.
			theString at:index put:thisChar.
			thisChar := self next
		    ]
		]
	    ] ifFalse:[
		inPrimitive ifFalse:[
		    (thisChar == sep) ifTrue:[
			(self peek == sep) ifFalse:[
			    done := true
			] ifTrue:[
			    self next
			]
		    ]
		]
	    ]
	].
	done ifFalse:[
	    index := index + 1.
	    theString at:index put:thisChar.
	    thisChar := self next
	]
    ].
    (index == 0) ifTrue:[^ ''].
    ^ theString copyTo:index
! !

!PeekableStream methodsFor:'positioning'!

skipAny:skipCollection
    "skip all characters included in the argument-set.
     returns the next peeked element or nil, if the end-of-stream was reached."

    |nextOne|

    nextOne := self peekOrNil.
    [nextOne notNil and:[skipCollection includes:nextOne]] whileTrue:[
        self next.
        nextOne := self peekOrNil
    ].
    ^ nextOne

    "
     |s skipChars|

     s := ReadStream on:'some numbers1234with\in other99 stuff' withCRs.
     skipChars := 'abcdefghijklmnopqrstuvwxyz\ ' withCRs.
     s skipAny:skipChars.
     Transcript showCR:(Integer readFrom:s).
     s skipAny:skipChars.
     Transcript showCR:(Integer readFrom:s).
    "
!

skipSeparators
    "skip all whitespace; returns the next peeked element or
     nil, if the end-of-stream was reached.
     The streams elements should be characters.
     Notice: compare this method to skipSpaces"

    |nextOne|

    nextOne := self peekOrNil.
    [nextOne notNil and:[nextOne isSeparator]] whileTrue:[
        self next.
        nextOne := self peekOrNil
    ].
    ^ nextOne

    "
     |s|

     s := ReadStream on:'one      two\three' withCRs.
     s skipSeparators.
     Transcript showCR:(s nextWord).
     s skipSeparators.
     Transcript showCR:(s nextWord).
     s skipSeparators.
     Transcript showCR:(s next displayString).
    "
!

skipSeparatorsExceptCR
    "skip all whitespace except carriage return; returns the 
     next peeked element or nil, if the end-of-stream was reached.
     The streams elements should be characters.
     Notice: compare this method to skipSpaces and skipSeparators"

    |nextOne|

    nextOne := self peekOrNil.
    [nextOne notNil 
     and:[nextOne isSeparator
     and:[nextOne ~~ Character cr]]] whileTrue:[
        self next.
        nextOne := self peekOrNil
    ].
    ^ nextOne
!

skipSpaces
    "skip all spaces; returns the next peeked element or
     nil, if the end-of-stream was reached.
     The streams elements should be characters.
     Notice: this one skips only spaces (i.e. no cr, tabs etc)
             usually, skipSeparators is what you want."

    |nextOne|

    nextOne := self peekOrNil.
    [nextOne notNil and:[nextOne == Character space]] whileTrue:[
        self next.
        nextOne := self peekOrNil
    ].
    ^ nextOne

    "
     |s|

     s := ReadStream on:'one      two\three' withCRs.
     s skipSpaces.
     Transcript showCR:(s nextWord).
     s skipSpaces.
     Transcript showCR:(s nextWord).
     s skipSpaces.
     Transcript showCR:(s next displayString).
    "
! !

!PeekableStream methodsFor:'reading'!

nextDecimalInteger
    "read the next integer in radix 10. Does NOT skip initial whitespace.
     The streams elements should be characters.
     Be careful - this method returns 0 if not posiioned on a digit intitially
     or if the end of the stream is encountered."

    |nextOne value|

    nextOne := self peekOrNil.
    value := 0.
    [nextOne notNil and:[nextOne isDigitRadix:10]] whileTrue:[
        value := (value * 10) + nextOne digitValue.
        self next.
        nextOne := self peekOrNil
    ].
    ^ value

    "
     |s|

     s := '1234 5678' readStream.
     s nextDecimalInteger. 
    "

    "
     |s|

     s := '1234 5678' readStream.
     s nextDecimalInteger.
     s skipSpaces.
     s nextDecimalInteger. 
    "
!

nextDelimited:terminator
    "return the contents of the receiver, up to the next terminator character. 
     Doubled terminators indicate an embedded terminator character.  
     For example: 'this '' was a quote'. 
     Start postioned before the initial terminator."

    | out ch |

    out := WriteStream on: (String new: 1000).
    self atEnd ifTrue: [^ ''].
    self next == terminator ifFalse: [self skip: -1].       "absorb initial terminator"
    [(ch := self next) == nil] whileFalse: [
        (ch == terminator) ifTrue: [
            self peek == terminator ifFalse: [
                ^ out contents  "terminator is not doubled; we're done!!"
            ].
            self next.  "skip doubled terminator"
        ].
        out nextPut: ch.
    ].
    ^ out contents

    "
     ('*foo bar baz* more foo' readStream nextDelimited:$*) 
     ('*foo bar **baz***' readStream nextDelimited:$*)   
    "
!

nextPeek
    "advance to next element and return the peeked element"

    self next.
    ^ self peek
!

peek 
    "return the next element of the stream without advancing (i.e.
     the following send of next will return this element again.)
     - we do not know here how to do it, it must be redefined in subclass"

    ^ self subclassResponsibility
!

peekFor:anObject 
    "if the next-to-be-read object is equal to the argument, anObject, read it
     and return true. Otherwise, leave the receiver unaffected and return false."

    self peek = anObject ifTrue:[
	self next.
	^ true
    ].
    ^ false
!

upToMatching:aBlock
    "Return the next elements up to but not including the next element
     for which aBlock returns true.
     The next read will return that matching element."

    |answerStream element|

    answerStream := WriteStream on:(self contentsSpecies new).
    [self atEnd] whileFalse: [
        element := self peek.
        (aBlock value:element) ifTrue: [^ answerStream contents].
        answerStream nextPut:element.
        self next.
    ].
    ^ answerStream contents

    "
     'hello world' readStream upToMatching:[:c | c isSeparator].
    "
    "
     |s|

     s := 'hello world' readStream.
     s upToMatching:[:c | c isSeparator].
     s upToEnd
    "

    "Modified: 26.2.1997 / 12:20:57 / cg"
!

upToSeparator
    "Return the next elements up to but not including the next separator.
     The next read will return the separator.
     If no separator is encountered, the contents up to the end is returned.
     The elements are supposed to understand #isSeparator 
     (i.e. the receiver is supposed to be a character-stream)."

    ^ self upToMatching:[:ch | ch isSeparator]

    "
     'hello world' readStream upToSeparator  
     'helloworld' readStream upToSeparator   
     'helloworld' readStream upToSeparator   
     '' readStream upToSeparator   

     |s|
     s := 'hello world' readStream.
     s upToSeparator.
     s upToEnd  
    "

    "Modified: 4.1.1997 / 23:38:05 / cg"
! !

!PeekableStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/PeekableStream.st,v 1.21 2000-05-22 11:11:09 cg Exp $'
! !