PeekableStream.st
author Claus Gittinger <cg@exept.de>
Tue, 13 Jul 2004 10:39:04 +0200
changeset 8443 7bc4348c059e
parent 8192 ade8d06d98eb
child 8485 d94728eaf4f0
permissions -rw-r--r--
fileIn stuff moved to peekableStream

"
 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:'ErrorDuringFileInSignal CurrentFileInDirectoryQuerySignal'
	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 class methodsFor:'initialization'!

initialize
    "setup the signal used to handle errors during fileIn"

    ErrorDuringFileInSignal isNil ifTrue:[
        ErrorDuringFileInSignal := Error newSignalMayProceed:true.
        ErrorDuringFileInSignal nameClass:self message:#errorDuringFileInSignal.
        ErrorDuringFileInSignal notifierString:'error during fileIn'.

        CurrentFileInDirectoryQuerySignal := QuerySignal new.
        CurrentFileInDirectoryQuerySignal nameClass:self message:#currentFileInDirectoryQuerySignal.
        CurrentFileInDirectoryQuerySignal notifierString:'query for current directory when filing in'.
        CurrentFileInDirectoryQuerySignal handlerBlock:[:ex | ex proceedWith:Filename currentDirectory].
    ]

    "
     self initialize
    "
! !

!PeekableStream class methodsFor:'Signal constants'!

currentFileInDirectoryQuerySignal
    "return the querySignal, which can be used to ask for the current directory
     during a fileIn (that is the directory where the filed-in file resides),
     and in a fileBrowsers doIt.
     Using this, allows for the loaded code or doIts to ask for the fileBrowsers
     current directory, by asking this querySignal (which is nice sometimes)."

    ^ CurrentFileInDirectoryQuerySignal
! !

!PeekableStream class methodsFor:'queries'!

currentFileInDirectory
    "during a fileIn (if a script), the script can ask for the current directory"

    ^ CurrentFileInDirectoryQuerySignal query
! !

!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.
"/            thisChar == Character return ifTrue:[
"/                self peekOrNil == Character lf ifTrue:[
"/                    thisChar := Character lf.
"/                    self next.
"/                ]
"/            ].
            theString at:index put:thisChar.
            thisChar := self next.
        ]
    ].
    (index == 0) ifTrue:[^ ''].
    ^ theString copyTo:index
! !

!PeekableStream methodsFor:'fileIn'!

askForDebug:message
    "launch a box asking if a debugger is wanted - used when an error
     occurs while filing in"

    ^ self askForDebug:message canContinueForAll:false
!

askForDebug:message canContinueForAll:canContinueForAll
    "launch a box asking if a debugger is wanted - used when an error
     occurs while filing in"

    |labels values|

    Smalltalk isInitialized ifFalse:[
        'PositionableStream [warning]: fileIn error during startup: ' errorPrint. message errorPrintCR.
        ^ #debug
    ].
    "/
    "/ are we in the startup sequence of an image restart ?
    "/
    Processor activeProcessIsSystemProcess ifTrue:[
        'PositionableStream [warning]: fileIn error during startup: ' errorPrint. message errorPrintCR.
        ^ #continue
    ].

    canContinueForAll ifTrue:[
          labels := #('Cancel' 'Skip' 'Debug' 'Dont ask again' 'Continue').
          values := #(#abort   #skip  #debug  #continueForAll #continue).
    ] ifFalse:[
          labels := #('Cancel' 'Skip' 'Debug' 'Continue').
          values := #(#abort  #skip   #debug #continue).
    ].
    AbortAllSignal isHandled ifTrue:[
      labels := #('Cancel All') , labels.
      values := #(#cancelAll) , values.
    ].

    ^ OptionBox 
          request:message 
          label:'Error in fileIn'
          image:(WarningBox iconBitmap)
          buttonLabels:labels
          values:values
          default:#continue
          onCancel:#abort.

    "Modified: 10.1.1997 / 18:00:56 / cg"
!

basicFileInNotifying:someone passChunk:passChunk
    "central method to file in from the receiver, i.e. read chunks and evaluate them -
     return the value of the last chunk.
     Someone (which is usually some codeView) is notified of errors."

    |lastValue pkg spc spaces
     packageQuerySignal nameSpaceQuerySignal usedNameSpaceQuerySignal
     changeDefaultApplicationNotificationSignal
     defaultApplicationQuerySignal defaultApplication
     confirmationQuerySignal handledSignals passedSignals
     dontAskSignals askSomeoneForPackage redef outerContext|

    self skipSeparators.
    lastValue := self peek.
    lastValue == $< ifTrue:[
        "/ assume, its an xml file
        ^ self fileInXMLNotifying:someone passChunk:passChunk.
    ].
    lastValue == $# ifTrue:[
        "assume unix interpreter name:
         '#!!stx -e' or something like this"
        self nextPeek == $!! ifTrue:[
            "skip the unix command line"
            self nextLine
        ] ifFalse:[
             self error:'Invalid chunk start'
        ]
    ].

    Smalltalk::Compiler isNil ifTrue:[
        self isFileStream ifTrue:[
            Transcript show:('[' , self pathName , '] ').
        ].
        Transcript showCR:'cannot fileIn (no compiler).'.
        ^ nil.
    ].

    "/ support for V'Age applications
    defaultApplicationQuerySignal := Class defaultApplicationQuerySignal.
    changeDefaultApplicationNotificationSignal := Class changeDefaultApplicationNotificationSignal.

    "/ support for ST/X's namespaces & packages
    packageQuerySignal := Class packageQuerySignal.
    nameSpaceQuerySignal := Class nameSpaceQuerySignal.
    usedNameSpaceQuerySignal := Class usedNameSpaceQuerySignal.

    (someone respondsTo:#packageToInstall) ifFalse:[
        pkg := packageQuerySignal query.
        askSomeoneForPackage := false.
    ] ifTrue:[
        pkg := someone packageToInstall.
        askSomeoneForPackage := true.
    ].
    (someone respondsTo:#currentNameSpace) ifFalse:[
        spc := nameSpaceQuerySignal query.
    ] ifTrue:[
        spc := someone currentNameSpace
    ].
    (someone respondsTo:#usedNameSpaces) ifFalse:[
        spaces := usedNameSpaceQuerySignal query.
    ] ifTrue:[
        spaces := someone usedNameSpaces
    ].
    (someone respondsTo:#defaultApplication) ifFalse:[
        defaultApplication := defaultApplicationQuerySignal query.
    ] ifTrue:[
        defaultApplication := someone defaultApplication
    ].

    confirmationQuerySignal := Metaclass confirmationQuerySignal.

    passedSignals := IdentitySet new.

    handledSignals := SignalSet new.
    handledSignals add:changeDefaultApplicationNotificationSignal.
    passedSignals add:changeDefaultApplicationNotificationSignal.
    handledSignals add:defaultApplicationQuerySignal.
    passedSignals add:defaultApplicationQuerySignal.

    handledSignals add:packageQuerySignal.
    handledSignals add:usedNameSpaceQuerySignal.
    handledSignals add:nameSpaceQuerySignal.

    handledSignals add:Error.
    passedSignals add:Error.

    handledSignals add:(Class methodRedefinitionSignal).
    passedSignals add:(Class methodRedefinitionSignal).
    handledSignals add:(Class classRedefinitionSignal).
    passedSignals add:(Class classRedefinitionSignal).
    handledSignals add:confirmationQuerySignal.
    passedSignals add:confirmationQuerySignal.

    outerContext := thisContext.

    handledSignals handle:[:ex |
        |sig action what sender msg param oldPackage newPackage proceedValue
         canContinueForAll|

        sig := ex signal.
"/sig == packageQuerySignal ifTrue:[
"/self halt.
"/].
        (passedSignals includes:sig) ifTrue:[
            (sig isHandledIn:outerContext) ifTrue:[
                ex reject
            ]
        ].
        
        sig == changeDefaultApplicationNotificationSignal ifTrue:[
            "/ invoked via #becomeDefault to set the defaultApp and the package.
            "/ (only when filing in V'Age code)
            defaultApplication := ex parameter.
            pkg := defaultApplication name asSymbol.
            ex proceedWith:nil
        ].
        sig == defaultApplicationQuerySignal ifTrue:[
            "/ query for the application to add classes & methods into
            "/ (only when filing in V'Age code)
            ex proceedWith:defaultApplication
        ].
        sig == packageQuerySignal ifTrue:[
            "/ query for the package to use for classes & methods
            askSomeoneForPackage ifTrue:[
                ex proceedWith:someone packageToInstall
            ] ifFalse:[
                ex proceedWith:pkg
            ]
        ].
        sig == usedNameSpaceQuerySignal ifTrue:[
            "/ query for the namespaces searched when encountering globals
            ex proceedWith:spaces
        ].
        sig == nameSpaceQuerySignal ifTrue:[
            "/ query for the namespace to install new classes in
            ex proceedWith:spc
        ].
        sig == confirmationQuerySignal ifTrue:[
            ex proceedWith:false "/ no dialogs popping up
        ].

        sig == Stream endOfStreamSignal ifTrue:[
            ex reject
        ].

        sig == Signal noHandlerSignal ifTrue:[
            ex parameter rejected ifTrue:[
                ex reject
            ].
        ].

        (dontAskSignals notNil and:[dontAskSignals includesKey:sig]) ifTrue:[
            ex proceedWith:(dontAskSignals at:sig)
        ].

        canContinueForAll := false.
        redef := false.

        "/ for your convenience ...
        (sig == Class methodRedefinitionSignal) ifTrue:[
            param := ex parameter. "/ an association: oldMethod -> newMethod
            oldPackage := param key package.
            newPackage := param value package.
            msg := 'trying to overwrite method:\\    ' , param key whoString , '\\in package ''' 
                   , oldPackage , ''' with method from package ''' , newPackage , ''''.
            canContinueForAll := true.
        ] ifFalse:[
            (sig == Class classRedefinitionSignal) ifTrue:[
                param := ex parameter. "/ an association: oldClass -> newClass
                
                oldPackage := param key package.
                newPackage := param value package.
                msg := 'trying to redefine class: ' , param key name allBold , '\\in package ''' 
                       , oldPackage , ''' with new definition from package ''' , newPackage , ''''.
                canContinueForAll := true.
                redef := true.
            ] ifFalse:[
                msg := 'error in fileIn: %1'
            ]
        ].

        what := ex description.
        what isNil ifTrue:[
            what := ex signal notifierString.
        ].

        msg := msg bindWith:what.

        "/ handle the case where no GUI has been built in,
        "/ just abort the fileIn with a notification

        Display isNil ifTrue:[
            sender := ex suspendedContext sender.
            msg := msg , ('\\in ' , sender receiver class name , '>>>' , sender selector) withCRs.
            self notify:msg.
            ex return
        ].

        sig == HaltInterrupt ifTrue:[
            sender := ex suspendedContext.
            msg := msg , ('\\in ' , sender receiver class name , '>>>' , sender selector) withCRs
        ].

        "/ otherwise ask what should be done now and either
        "/ continue or abort the fileIn

        redef ifTrue:[
            action := OptionBox 
                          request:(msg withCRs) 
                          label:'Class redefinition in fileIn'
                          image:(WarningBox iconBitmap)
"/ cg: now always keep the old packageID
"/                          buttonLabels:#('cancel' 'skip' 'debug' 'keep' 'keep all' 'continue' 'continue all')
"/                          values:#(#abort #skip #debug #keep #keepAll #continue #continueForAll)
                          buttonLabels:#('Cancel' 'Skip' 'Debug' 'Continue' 'Continue All')
                          values:#(#abort #skip #debug #keep #keepAll)
                          default:#keep
                          onCancel:#abort.
        ] ifFalse:[
            action := self askForDebug:msg withCRs canContinueForAll:canContinueForAll.
        ].
        action == #continueForAll ifTrue:[
            dontAskSignals isNil ifTrue:[
                dontAskSignals := IdentityDictionary new.
            ].
            dontAskSignals at:sig put:#continue.
            action := proceedValue := #continue.
        ] ifFalse:[
            action == #keepForAll ifTrue:[
                dontAskSignals isNil ifTrue:[
                    dontAskSignals := IdentityDictionary new.
                ].
                dontAskSignals at:sig put:#keep.
                action := #continue.
                proceedValue := #keep.
            ] ifFalse:[
                action == #keep ifTrue:[
                    action := #continue.
                    proceedValue := #keep.
                ].
            ].
        ].

        action == #continue ifTrue:[
            ex proceedWith:proceedValue
        ].
        action == #abort ifTrue:[
            AbortSignal raise.
            ex return
        ].
        action == #cancelAll ifTrue:[
            AbortAllSignal raise.
            ex return
        ].
        action == #skip ifTrue:[
            ex proceedWith:nil
        ].
        action == #debug ifTrue:[
            Debugger enter:ex suspendedContext 
                     withMessage:ex description 
                     mayProceed:true.
            ex proceedWith:proceedValue
        ].

        "/ (ex signal) enterDebuggerWith:ex message:what.
        ex reject
    ] do:[
        [self atEnd] whileFalse:[
            lastValue := self fileInNextChunkNotifying:someone passChunk:passChunk
        ]
    ].
    ^ lastValue

    "Modified: / 10.9.1999 / 16:54:01 / stefan"
    "Modified: / 16.11.2001 / 16:21:28 / cg"
!

fileIn
    "file in from the receiver, i.e. read chunks and evaluate them -
     return the value of the last chunk."

    |notifiedLoader|

    SourceFileLoader notNil ifTrue:[
        notifiedLoader := SourceFileLoader on:self.
    ].

    ^ self fileInNotifying:notifiedLoader passChunk:true.
!

fileInBinary
    "file in from the receiver, i.e. read binary stored classes and/or objects.
     Return the last object."

    |bos obj|

    bos := BinaryObjectStorage onOld:self.
    Class nameSpaceQuerySignal 
	answer:Smalltalk
	do:[
	    [self atEnd] whileFalse:[
		obj := bos next.
	    ]
	].
    bos close.
    ^ obj

    "Created: / 13.11.2001 / 10:12:30 / cg"
    "Modified: / 13.11.2001 / 10:14:04 / cg"
!

fileInNextChunkNotifying:someone
    "read next chunk, evaluate it and return the result;
     someone (which is usually some codeView) is notified of errors.
     Filein is done as follows:
	read a chunk
	if it started with an excla, evaluate it, and let the resulting object
	fileIn more chunks.
	This is a nice trick, since the methodsFor: expression evaluates to
	a ClassCategoryReader which reads and compiles chunks for its class.
	However, other than methodsFor expressions are possible - you can
	(in theory) create readers for any syntax.
    "

    ^ self fileInNextChunkNotifying:someone passChunk:false
!

fileInNextChunkNotifying:someone passChunk:passChunk
    "read next chunk, evaluate it and return the result;
     someone (which is usually some codeView) is notified of errors.
     Filein is done as follows:
	read a chunk
	if it started with an excla, evaluate it, and let the resulting object
	fileIn more chunks.
	This is a nice trick, since the methodsFor: expression evaluates to
	a ClassCategoryReader which reads and compiles chunks for its class.
	However, other than methodsFor expressions are possible - you can
	(in theory) create readers for any syntax.
    "

    ^ self fileInNextChunkNotifying:someone passChunk:passChunk silent:nil
!

fileInNextChunkNotifying:someone passChunk:passChunk silent:beSilent
    "read next chunk, evaluate it and return the result;
     someone (which is usually some codeView) is notified of errors.
     Filein is done as follows:
	read a chunk
	if it started with an excla, evaluate it, and let the resulting object
	fileIn more chunks.
	This is a nice trick, since the methodsFor: expression evaluates to
	a ClassCategoryReader which reads and compiles chunks for its class.
	However, other than methodsFor expressions are possible - you can
	(in theory) create readers for any syntax.
    "

    |aString sawExcla rslt done|

    self skipSeparators.
    self atEnd ifFalse:[
	sawExcla := self peekFor:(self class chunkSeparator).
	aString := self nextChunk.
	"/
	"/ handle empty chunks;
	"/ this allows for Squeak code to be filedIn
	"/
	[aString size == 0
	and:[self atEnd not]] whileTrue:[
	    aString := self nextChunk.
	].
	aString size ~~ 0 ifTrue:[
	    passChunk ifTrue:[
		someone notNil ifTrue:[someone source:aString]
	    ].
	    sawExcla ifFalse:[
		rslt := Smalltalk::Compiler evaluate:aString notifying:someone.
	    ] ifTrue:[
		Smalltalk::Compiler emptySourceNotificationSignal handle:[:ex |
		    ^ nil
		] do:[
		    rslt := Smalltalk::Compiler evaluate:aString notifying:someone compile:false.
		].

		"
		 usually, the above chunk consists of some methodsFor:-expression
		 in this case, the returned value is a ClassCategoryReader,
		 which is used to load & compile the methods ...
		"
		rslt isNil ifTrue:[
		    "
		     however, if that was nil (i.e. some error), we skip chunks
		     up to the next empty chunk.
		    "
		    Transcript showCR:'skipping chunks ...'.
		    done := false.
		    [done] whileFalse:[
			aString := self nextChunk.
			done := (aString size == 0).
		    ]
		] ifFalse:[
		    rslt := rslt 
				fileInFrom:self 
				notifying:someone 
				passChunk:passChunk
				single:false
				silent:beSilent
		]
	    ]
	]
    ].
    ^ rslt

    "Modified: 14.10.1997 / 17:10:35 / cg"
!

fileInNotifying:notifiedLoader passChunk:passChunk
    "central method to file in from the receiver, i.e. read chunks and evaluate them -
     return the value of the last chunk.
     Someone (which is usually some codeView) is notified of errors."

    self isFileStream ifFalse:[
        ^ self basicFileInNotifying:notifiedLoader passChunk:passChunk.
    ].

    ^ self fileInNotifying:notifiedLoader passChunk:passChunk inDirectory:(self pathName asFilename directory).
!

fileInNotifying:notifiedLoader passChunk:passChunk inDirectory:aDirectory
    "central method to file in from the receiver, i.e. read chunks and evaluate them -
     return the value of the last chunk.
     Someone (which is usually some codeView) is notified of errors."

    |oldPath val thisDirectory thisDirectoryPathName|

    thisDirectory := aDirectory asFilename.
    thisDirectoryPathName := thisDirectory pathName.
    oldPath := Smalltalk systemPath.

    [   
        Smalltalk systemPath:(oldPath copy addFirst:thisDirectoryPathName; yourself).
        CurrentFileInDirectoryQuerySignal answer:thisDirectory do:[
            val := self basicFileInNotifying:notifiedLoader passChunk:passChunk.
        ]
    ] ensure:[
        "take care, someone could have changed SystemPath during fileIn!!"
        (Smalltalk systemPath copyFrom:2) = oldPath ifTrue:[
            Smalltalk systemPath:oldPath.
        ] ifFalse:[
            (oldPath includes:thisDirectoryPathName) ifFalse:[
                Smalltalk systemPath remove:thisDirectoryPathName ifAbsent:[].
                Smalltalk flushPathCaches.
            ].
        ].
    ].
    ^ val
!

fileInXMLNotifying:someone passChunk:passChunk
    "filein an XML source file (format as in campSmalltalk DTD)"

    | builder parser|

    (XML isNil or:[XML::SourceNodeBuilder isNil or:[XML::XMLParser isNil]]) ifTrue:[
	Smalltalk loadPackage:'stx:goodies/xml/vw'.
	(XML isNil or:[XML::SourceNodeBuilder isNil or:[XML::XMLParser isNil]]) ifTrue:[
	    self error:'Could not load XML package(s) from ''stx:goodies/xml/vw'''.
	]
    ].

    builder := XML::SourceNodeBuilder new.
    parser := XML::XMLParser on:self.
    parser builder:builder.
    parser validate:false.
    parser scanDocument.
    "/ self halt.
! !

!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 uninitializedNew: 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.24 2004-07-13 08:38:59 cg Exp $'
! !

PeekableStream initialize!