PositionableStream.st
author Claus Gittinger <cg@exept.de>
Sat, 22 Mar 1997 16:19:44 +0100
changeset 2484 05bd2cc43192
parent 2432 5338f9b60a66
child 2559 c1e87dd81a13
permissions -rw-r--r--
#privateClasses now returns an unsorted set; use #privateClassesSorted for old behavior.

"
 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.
"

PeekableStream subclass:#PositionableStream
	instanceVariableNames:'collection position readLimit writeLimit'
	classVariableNames:'ErrorDuringFileInSignal ChunkSeparator'
	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.

    [author:]
	Claus Gittinger
"
! !

!PositionableStream class methodsFor:'initialization'!

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

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

	ChunkSeparator := $!!
    ]
! !

!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:'constants'!

chunkSeparator
    "return the chunk-separation character"

    ^ ChunkSeparator
! !

!PositionableStream methodsFor:'accessing'!

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
!

peekFor:something
    "return true and move past if next == something; 
     otherwise stay and let position unchanged"

    self next == something ifTrue:[
	^ true
    ].
    self backStep.
    ^ false
!

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: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
! !

!PositionableStream 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
!

nextChunkPut:aString
    "put aString as a chunk onto the receiver;
     double all exclamation marks except within primitives and append a 
     single delimiting exclamation mark at the end.
     This modification of the chunk format (not doubling exclas in primitive code)
     was done to have primitive code more readable and easier be edited in the fileBrowser
     or other editors.
     Its no incompatibility, since inline primitives are an ST/X special
     and code containing ST/X primitives cannot be loaded into other smalltalks anyway."

    self nextPutAllAsChunk:aString.
    self nextPut:ChunkSeparator

    "Modified: 9.12.1995 / 15:56:54 / cg"
!

nextPutAllAsChunk:aString
    "put aString as a chunk onto the receiver;
     double all exclamation marks except within primitives.
     This modification of the chunk format (not doubling exclas in primitive code)
     was done to have primitive code more readable and easier be edited in the fileBrowser
     or other editors.
     Its no incompatibility, since inline primitives are an ST/X special
     and code containing ST/X primitives cannot be loaded into other smalltalks anyway."

    |sep stopChars inPrimitive character
     index    "{ Class:SmallInteger }"
     endIndex "{ Class:SmallInteger }"
     stop     "{ Class:SmallInteger }"
     next     "{ Class:SmallInteger }"|

    sep := ChunkSeparator.
    stopChars := '{}' copyWith:sep.

    inPrimitive := false.
    index := 1.
    endIndex := aString size.
    stop := endIndex + 1.

    [index <= endIndex] whileTrue:[
	"
	 find position of next interesting character; 
	 output stuff up to that one in one piece
	"
	next := aString indexOfAny:stopChars startingAt:index ifAbsent:stop.

	((index == 1) and:[next == stop]) ifTrue:[
	    self nextPutAll:aString
	] ifFalse:[
	    self nextPutAll:aString startingAt:index to:(next - 1)
	].

	index := next.
	(index <= endIndex) ifTrue:[
	    character := aString at:index.

	    (character == ${ ) ifTrue:[
		"/ starts a primitive
		((index > 1) and:[(aString at:index-1) == $%]) ifTrue:[
		    inPrimitive := true
		]
	    ] ifFalse:[
		"/ ends a primitive
		(character == $} ) ifTrue:[
		    ((index > 1) and:[(aString at:index-1) == $%]) ifTrue:[
			inPrimitive := false
		    ]
		] ifFalse:[
		    "/
		    "/ exclas have to be doubled - except if within a primitive
		    "/
		    inPrimitive ifFalse:[
			(character == sep) ifTrue:[
			    self nextPut:sep
			]
		    ]
		]
	    ].

	    self nextPut:character.
	    index := index + 1
	]
    ].

    "Modified: 9.12.1995 / 15:56:47 / cg"
!

nextPutChunkSeparator
    "append a chunk separator character"

    self nextPut:ChunkSeparator

    "Created: 13.9.1995 / 17:39:26 / claus"
! !

!PositionableStream methodsFor:'fileIn'!

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

    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
    ].

    ^ OptionBox 
          request:message 
          label:'Error in fileIn'
          form:(WarningBox iconBitmap)
          buttonLabels:#('cancel' 'debug' 'continue')
          values:#(#abort #debug #continue)
          default:#continue.

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

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

    ^ self fileInNotifying:(SourceFileLoader on:self) passChunk:true
!

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.
    "

    |aString sawExcla rslt done|

    self skipSeparators.
    self atEnd ifFalse:[
	sawExcla := self peekFor:ChunkSeparator.
	aString := self nextChunk.
	aString size ~~ 0 ifTrue:[
	    passChunk ifTrue:[
		someone source:aString
	    ].
	    sawExcla ifFalse:[
		rslt := Compiler evaluate:aString notifying:someone.
	    ] ifTrue:[
		rslt := 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) or:[aString isEmpty].
		    ]
		] ifFalse:[
		    rslt := rslt fileInFrom:self notifying:someone  passChunk:passChunk
		]
	    ]
	]
    ].
    ^ rslt

    "Modified: 18.5.1996 / 15:44:21 / cg"
!

fileInNotifying:someone passChunk:passChunk
    "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 queries pkg spc spaces
     packageQuerySignal nameSpaceQuerySignal usedNameSpaceQuerySignal
     methodRedefinitionSignal|

    packageQuerySignal := Class packageQuerySignal.
    nameSpaceQuerySignal := Class nameSpaceQuerySignal.
    usedNameSpaceQuerySignal := Class usedNameSpaceQuerySignal.

    queries := SignalSet with:packageQuerySignal
                         with:nameSpaceQuerySignal
                         with:usedNameSpaceQuerySignal.

    queries handle:[:ex |
        ex signal == packageQuerySignal ifTrue:[
            pkg isNil ifTrue:[
                (someone respondsTo:#packageToInstall) ifFalse:[
                    pkg := packageQuerySignal raise.
                ] ifTrue:[
                    pkg := someone packageToInstall
                ].
            ].
            ex proceedWith:pkg
        ].
        ex signal == nameSpaceQuerySignal ifTrue:[
            spc isNil ifTrue:[
                (someone respondsTo:#currentNameSpace) ifFalse:[
                    spc := nameSpaceQuerySignal raise.
                ] ifTrue:[
                    spc := someone currentNameSpace
                ].
            ].
            ex proceedWith:spc
        ].
        ex signal == usedNameSpaceQuerySignal ifTrue:[
            spaces isNil ifTrue:[
                (someone respondsTo:#usedNameSpaces) ifFalse:[
                    spaces := usedNameSpaceQuerySignal raise.
                ] ifTrue:[
                    spaces := someone usedNameSpaces
                ].
            ].
            ex proceedWith:spaces
        ].
    ] do:[
        |methodRedefinitionSignal|

        methodRedefinitionSignal := Class methodRedefinitionSignal.

        "
         catch any errors during fileIn 
         - offer debug/abort/continue choice
        "
        ErrorSignal handle:[:ex |
            |action what sender msg param oldPackage newPackage|

            "/ for your convenience ...
            ex signal == methodRedefinitionSignal ifTrue:[
                param := ex parameter. "/ an association: oldMethod -> newMethod
                oldPackage := param key package.
                newPackage := param value package.
                msg := 'trying to overwrite method:\\    %1\\in package ''' 
                       , oldPackage , ''' with method from package ''' , newPackage , ''''
            ] ifFalse:[
                msg := 'error in fileIn: %1'
            ].

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

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

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

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

            action := self askForDebug:(msg bindWith:what) withCRs.
            action == #continue ifTrue:[
                ex proceed
            ].
            action == #abort ifTrue:[
                ex return
            ].
            (ex signal) enterDebuggerWith:ex message:what.
            ex reject
        ] do:[
            [self atEnd] whileFalse:[
                lastValue := self fileInNextChunkNotifying:someone passChunk:passChunk
            ]
        ].
    ].
    ^ lastValue

    "Modified: 20.12.1996 / 00:00:13 / cg"
! !

!PositionableStream methodsFor:'positioning'!

backStep
    "move backward read position by one"

    position <= 0 ifTrue: [^ self positionError].
    position := position - 1
!

position
    "return the read position"

    ^ position
!

position:index
    "set the read position"

    "/ FIX: allow positioning right after last element of stream
    "/ ((index > readLimit) or:[index < 0]) ifTrue: [^ self positionError].

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

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

    position := "0" 1
!

setToEnd
    "set the read position to the end of the collection"

    position := readLimit
!

skip:numberToSkip
    "skip the next numberToSkip elements"

    self position:(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 l first idx|

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

    "
     |s|
     s := ReadStream on:'12345678901234567890'.
     s skipThroughAll:'901'.
     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 l first idx|

    oldPos := self position.
    l := aCollection size.
    first := aCollection at:1.
    [self atEnd] whileFalse:[
	buffer := self next:l.
	buffer = aCollection ifTrue:[
	    self position:(self position - l).
	    ^ self
	].
	idx := buffer indexOf:first startingAt:2.
	idx == 0 ifFalse:[
	    self position:(self position - l + idx - 1)
	]
    ].
    self position:oldPos.
    ^ nil

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

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

!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.
    position := "0" 1
!

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

    collection := aCollection.
    position := first.
    readLimit := last
!

positionError
    "{ Pragma: +optSpace }"

    "report an error when positioning past the end"

    ^ self error:'cannot position past end of collection'
!

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

    collection := aCollection.
    self setToEnd
! !

!PositionableStream methodsFor:'queries'!

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

    ^ true
! !

!PositionableStream methodsFor:'testing'!

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

    ^ position > readLimit
!

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

    ^ readLimit == 0
! !

!PositionableStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/PositionableStream.st,v 1.55 1997-03-01 16:28:32 cg Exp $'
! !
PositionableStream initialize!