Stream.st
author claus
Fri, 25 Feb 1994 14:00:53 +0100
changeset 56 be0ed17e6f85
parent 50 71f3b9444905
child 62 e1b4369c61fb
permissions -rw-r--r--
*** empty log message ***

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

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

Stream comment:'

COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Stream.st,v 1.5 1994-02-05 12:24:58 claus Exp $
'!

!Stream class methodsFor:'instance creation'!

new
    "report an error - Streams are created using on:-messages"

    ^ self error:'Streams cannot be created with new'
! !

!Stream methodsFor:'accessing'!

contents
    "return the contents of the stream
     - we do not know here how to do it, it must be redefined in subclass"

    ^ self subclassResponsibility
! !

!Stream methodsFor:'accessing-reading'!

next
    "return the next element of the stream
     - we do not know here how to do it, it must be redefined in subclass"

    ^ self subclassResponsibility
!

next:count
    "return the next count elements of the stream as a Collection"

    |array|

    array := Array new:count.
    1 to:count do: [:index |
        array at:index put:(self next)
    ].
    ^ array
!

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

    self next.
    ^ self peek
!

nextMatchFor:anObject
    "read from the receiver, searching for the argument, anObject.
     if the end is reached, return nil; otherwise return the argument, 
     anObject. The next read operation will return the element after anObject."

    |nextElement|

    [self atEnd] whileFalse:[
        nextElement := self next.
        (nextElement == anObject) ifTrue: [ ^ nextElement ]
    ].
    ^ nil
!

skipFor:anObject
    "skip all objects up-to and including anObject; return the element after anObject."

    (self nextMatchFor:anObject) notNil ifTrue:[
        ^ self next
    ].
    ^ nil
!

skipThrough:anObject
    "skip all objects up-to and including anObject. The next read operation
     will return the element after anObject."

    ^ self nextMatchFor:anObject
! !

!Stream methodsFor:'accessing-writing'!

nextPut:anObject
    "put the argument, anObject onto the receiver
     - we do not know here how to do it, it must be redefined in subclass"

    ^ self subclassResponsibility
!

next:count put:anObject
    "put the argument, anObject count times onto the receiver"

    count timesRepeat:[self nextPut:anObject].
    ^ anObject
!

nextPutAll:aCollection
    "put all elements of the argument, aCollection onto the receiver"

    aCollection do:[:element |
        self nextPut:element
    ].
    ^ aCollection
!

nextPutAll:aCollection startingAt:first to:last
    "put the elements with index from first to last
     of the argument, aCollection onto the receiver"

    aCollection from:first to:last do:[:element |
        self nextPut:element
    ].
    ^ aCollection
!

endEntry
    "for compatibility with Transcript"

    ^ self
!

show:aString
    "put all elements of the argument, aString onto the receiver;
     this makes streams somewhat compatible to TextCollectors and
     allows you to say: Smalltalk at:#Transcript put:Stdout"

    ^ self nextPutAll:aString printString
!

showCr:aString
    "put all elements of the argument, aString onto the receiver;
     and append a newline.
     for compatibility with TextCollectors"

    self show:aString.
    self cr
! !

!Stream methodsFor:'closing'!

close
    "close the stream - nothing done here"

    ^ self
! !

!Stream methodsFor:'testing'!

atEnd
    "return true if the end of the stream has been reached;
     - we do not know here how to do it, it must be redefined in subclass"

    ^ self subclassResponsibility
! !

!Stream methodsFor:'enumerating'!

do:aBlock
    "evaluate the argument, aBlock for every element up to the end of the
     stream"

    [self atEnd] whileFalse:[
        aBlock value:(self next)
    ]
! !

!Stream methodsFor:'queries'!

isStream
    "return true, if the receiver is some kind of Stream."

    ^ true
!

lineLength
    "this is just a layout hint for prettyprinting functions
     - for compatibility with TextCollectors"

    ^ 80
! !

!Stream methodsFor: 'nonhomogeneous accessing'!

nextNumber: n 
        "Answer the next n bytes as a positive Integer."

        | s i |

        n <= 4 ifTrue:[
            s := 0.
            i := 0.
            [(i := i + 1) <= n] whileTrue: [s := ((s bitShift: 8) bitOr: self next)].
            ^ s
        ].
        s := 0.
        1 to: n do: [:j | s := s * 256 + self next].
        "reverse order of significance"
        ^s truncated
!

nextNumber: n put: v 
        "Append to the receiver the argument, v, which is a positive Integer,
         as the next n bytes.  Possibly pad with leading zeros."

        | vlen i |

        n < (vlen := v digitLength) ifTrue: [self error: 'number too big'].

        "pad with leading zeros"
        i := n.
        [i > vlen] whileTrue: [self nextPut: 0. i := i - 1].
        i = 1 ifTrue: [^self nextPut: v].
        [i > 0] whileTrue: [self nextPut: (v digitAt: i). i := i - 1]
! !