Stream.st
author Claus Gittinger <cg@exept.de>
Mon, 15 Jul 1996 09:08:44 +0200
changeset 1548 9186c76bc571
parent 1538 b62f12073403
child 1665 928e9a308cea
permissions -rw-r--r--
added #throughAll:

"
 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:'signalAtEnd'
	classVariableNames:'StreamErrorSignal PositionErrorSignal ReadErrorSignal
		WriteErrorSignal EndOfStreamSignal'
	poolDictionaries:''
	category:'Streams'
!

!Stream  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
"
    An abstract class defining common behavior for all stream-like objects.
    See concrete subclasses for more detail.

    The protocol as implemented here is often only provided as a fallBack
    for very uncommon cases. Much of it is redefined for performance.
    (In streams which know more about their internal representation ...)


    Subclasses should (at least) implement:
        #next           (if readable)
        #nextPut:       (if writable)
        #contents
        #atEnd
        #isReadable
        #isWritable

    Peekable & Positionable streams should (at least) implement:
        #peek
        #position
        #position:


    [Class variables:]
        StreamErrorSignal       <Signal>        parent of all stream errors

        PositionErrorSignal     <Signal>        position attemted on a stream
                                                which does not support positioning

        ReadErrorSignal         <Signal>        raised on read errors

        WriteErrorSignal        <Signal>        raised on write errors

        EndOfStreamSignal       <Signal>        raised at end of stream

    [author:]
        Claus Gittinger
"
! !

!Stream  class methodsFor:'initialization'!

initialize
    StreamErrorSignal isNil ifTrue:[
	StreamErrorSignal := ErrorSignal newSignalMayProceed:false.
	StreamErrorSignal nameClass:self message:#streamErrorSignal.
	StreamErrorSignal notifierString:'Stream error'.

	PositionErrorSignal := StreamErrorSignal newSignalMayProceed:true.
	PositionErrorSignal nameClass:self message:#positionErrorSignal.
	PositionErrorSignal notifierString:'stream as no concept of a position'.

	ReadErrorSignal := StreamErrorSignal newSignalMayProceed:false.
	ReadErrorSignal nameClass:self message:#readErrorSignal.
	ReadErrorSignal notifierString:'read error'.

	WriteErrorSignal := StreamErrorSignal newSignalMayProceed:false.
	WriteErrorSignal nameClass:self message:#writeErrorSignal.
	WriteErrorSignal notifierString:'write error'.

	EndOfStreamSignal := StreamErrorSignal newSignalMayProceed:false.
	EndOfStreamSignal nameClass:self message:#endOfStreamSignal.
	EndOfStreamSignal notifierString:'end of stream'.
    ]
! !

!Stream  class methodsFor:'instance creation'!

new
    "{ Pragma: +optSpace }"

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

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

!Stream  class methodsFor:'Signal constants'!

endOfStreamSignal
    "return the signal raised if read past end of stream is attemted"

    ^ EndOfStreamSignal
!

positionErrorSignal
    "return the signal raised if positioning is requested for
     a stream which does not support that kind of operation"

    ^ PositionErrorSignal
!

readErrorSignal
    "return the signal raised on read errors"

    ^ ReadErrorSignal
!

streamErrorSignal
    "return the parent of all stream errors;
     handling this one also handles all other errors.
     Also, this one may be raised for errors not related to read/write
     operations, such as failed ioctls in externalStream etc."

    ^ StreamErrorSignal
!

writeErrorSignal
    "return the signal raised on write errors"

    ^ WriteErrorSignal
! !

!Stream methodsFor:'accessing'!

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

    ^ self subclassResponsibility

    "Modified: 15.5.1996 / 17:36:29 / cg"
!

signalAtEnd
    "return the signalAtEnd flag setting. If true, reading past the end
     will raise an EndOfStream exception. If false, no exception is
     raised and nil is returned from all reading messages.
     The default is (currently) to NOT raise a signal."

    ^ signalAtEnd

    "Created: 5.2.1996 / 18:24:53 / stefan"
    "Modified: 15.5.1996 / 17:35:55 / cg"
!

signalAtEnd:aBoolean
    "set the signalAtEnd flag setting. If true, reading past the end
     will raise an EndOfStream exception. If false, no exception is
     raised and nil is returned from all reading messages.
     The default is (currently) to NOT raise a signal."

    signalAtEnd := aBoolean.

    "Created: 5.2.1996 / 18:24:53 / stefan"
    "Modified: 15.5.1996 / 17:36:12 / cg"
! !

!Stream methodsFor:'closing'!

close
    "close the stream - nothing done here.
     Added for compatibility with external streams."

    ^ self
! !

!Stream methodsFor:'emphasis'!

bold
    "set emphasis to #bold.
     this allows Streams to be used interchangeable with printStreams"

    self emphasis:#bold.

    "Created: 14.5.1996 / 17:37:37 / cg"
    "Modified: 3.6.1996 / 16:57:17 / cg"
!

boldItalic
    "set emphasis to #boldItalic
     this allows Streams to be used interchangeable with printStreams"

    self emphasis:#(bold italic).

    "Created: 14.5.1996 / 17:37:47 / cg"
    "Modified: 3.6.1996 / 17:15:22 / cg"
!

emphasis
    "ignored here - allows Streams to be used interchangable with
     text streams"

    ^ nil

    "Created: 14.5.1996 / 17:39:45 / cg"
!

emphasis:anEmphasis
    "ignored here.
     this allows Streams to be used interchangeable with printStreams"

    ^ self

    "Created: 14.5.1996 / 17:38:07 / cg"
!

italic 
    "set emphasis to #italic.
     this allows Streams to be used interchangeable with printStreams"

    self emphasis:#italic.

    "Created: 14.5.1996 / 17:37:55 / cg"
    "Modified: 3.6.1996 / 17:15:32 / cg"
!

normal
    "set emphasis to #normal.
     this allows Streams to be used interchangeable with printStreams"

    self emphasis:nil

    "Created: 14.5.1996 / 17:37:59 / cg"
    "Modified: 3.6.1996 / 17:15:35 / cg"
!

strikeout
    "set emphasis to #strikeout.
     this allows Streams to be used interchangeable with printStreams"

    self emphasis:#strikeout.

    "Modified: 3.6.1996 / 16:57:56 / cg"
    "Created: 3.6.1996 / 17:15:45 / cg"
!

underline
    "set emphasis to #underline.
     this allows Streams to be used interchangeable with printStreams"

    self emphasis:#underline.

    "Created: 3.6.1996 / 17:00:03 / cg"
    "Modified: 3.6.1996 / 17:15:38 / cg"
! !

!Stream methodsFor:'enumerating'!

do:aBlock
    "evaluate the argument, aBlock for all remaining elements,
     up to the end of the stream"

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

    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8 9).
     s next.
     s next.
     s do:[:element | Transcript showCR:element]
    "
! !

!Stream methodsFor:'error handling'!

pastEnd
    "someone tried to read after the end of the stream.
     if signalAtEnd == true, raise a signal.
     Otherwise return nil."

    signalAtEnd == true ifTrue:[
        ^ EndOfStreamSignal raiseIn:thisContext sender
    ].
    ^ nil

    "Created: 5.2.1996 / 21:56:08 / stefan"
! !

!Stream methodsFor:'misc'!

binary
    "switch to binary mode. In binary mode, reading of text streams
     returns byte-valued integers instead of characters; writing expects
     byte-valued integers respectively.
     Ignored here, but added to make internalStreams protocol compatible 
     with externalStreams."

    "Modified: 15.5.1996 / 17:38:36 / cg"
! !

!Stream methodsFor:'non homogenous reading'!

nextAlphaNumericWord
    "read the next word (i.e. up to non letter-or-digit).
     Return a string containing those characters.
     Any leading whitespace is skipped.
     This method does not advance over any non-alphanumeric characters;
     i.e. it will stick and continue to continue to return nil in this case. 
     Only call for it in a loop, AFTER you have checked for
     the next character to really be alphanumeric (using #peek)"

    |s c|

    [self atEnd not
     and:[(c := self peek) isSeparator]] whileTrue:[
        self next 
    ].

    self atEnd ifTrue:[^ nil].

    s := ''.

    [self atEnd not
     and:[(c := self peek) isLetterOrDigit]] whileTrue:[ 
        s := s copyWith:c. 
        self next 
    ].

    s size == 0 ifTrue:[^ nil].
    ^ s.

    "
     |s|

     s := 'hello world 1234 foo1 foo2' readStream.
     [s atEnd] whileFalse:[
        Transcript showCR:(s nextAlphaNumericWord).
     ].


   notice: streams end never reached this way (sticking at the '+'-character:
     |s|

     s := 'hello world 1234 foo1+foo2' readStream.
     10 timesRepeat:[
        Transcript showCR:(s nextAlphaNumericWord).
     ].
    "

    "Modified: 15.5.1996 / 17:51:42 / cg"
!

nextLine
    "return the characters upTo (but excluding) the next cr (carriage return)
     character (i.e. read a single line of text).
     Added for protocol compatibility with externalStreams."

    ^ self upTo:Character cr.

    "Modified: 11.7.1996 / 10:03:56 / cg"
!

nextLongMSB:msbFlag
    "return a signed long (4 bytes) from the stream.
     The receiver must support reading of binary bytes.

     The msbFlag argument controls if the integer is to be read with
     most-significant-byte-first (true) or least-first (false).
     This interface is provided to allow talking to external programs,
     where its known that the byte order is some definite one.
     If you dont care (i.e. talk to other smalltalks) or you can control the
     order, please use the corresponding xxxNet methods, which use a standard
     network byte order."

    |high uval "{ Class: SmallInteger }"|

    msbFlag ifTrue:[
        "most significant first"
        high := self next.
        uval := self next bitShift:16.
        uval := uval bitOr:(self next bitShift:8).
        uval := uval bitOr:(self next).
        uval := uval bitOr:(high bitShift:24).
    ] ifFalse:[
        "least significant first"
        uval := self next.
        uval := uval bitOr:(self next bitShift:8).
        uval := uval bitOr:(self next bitShift:16).
        uval := uval bitOr:(self next bitShift:24).
    ].
    "change from unsigned 0..FFFFFFFF to signed -80000000..7FFFFFFF"

"/ sorry- for now (2.7), stc cannot compile LargeInteger constants 
"/    uval >= 16r80000000 ifTrue:[
"/      ^ uval - 16r100000000 
"/    ].
"/ the following kludges around this
"/ well, new (2.8) can ...

    (uval bitShift:-16) >= 16r8000 ifTrue:[
        ^ uval - (16r10000000 bitShift:8)
    ].
    ^ uval

    "Modified: 11.7.1996 / 10:06:52 / cg"
!

nextLongNet
    "return a signed long (4 bytes) in network byte order from the stream.
     The receiver must support reading of binary bytes."

    ^ self nextLongMSB:(Socket networkLongOrderIsMSB)

    "Created: 10.1.1996 / 19:49:28 / cg"
!

nextNumber:n 
    "Return the next n bytes as a positive Integer; bytes are taken msb-first."

    |s 
     val "{ Class: SmallInteger }"
     rep "{ Class: SmallInteger }"|

    "claus: this method is central in binaryStorage -
     therefore it has been tuned a bit (and needs even more tuning)"

    n == 1 ifTrue:[
	^ self next
    ].
    n == 2 ifTrue:[
	val := self next.
	val := (val bitShift:8) + self next.
	^ val
    ].
    n == 3 ifTrue:[
	val := self next.
	val := (val bitShift:8) + self next.
	val := (val bitShift:8) + self next.
	^ val
    ].
    n == 4 ifTrue:[
	val := self next.
	val <= 16r3F ifTrue:[
	    val := (val bitShift:8) + self next.
	    val := (val bitShift:8) + self next.
	    val := (val bitShift:8) + self next.
	    ^ val
	].
	"sorry, but need a largeInteger"
	s := (val bitShift:8) + self next.
	s := (s bitShift:8) + self next.
	s := (s * 256) + self next.
	^ s
    ].

    "
     arbitrary long
    "
    s := 0.
    rep := n.
    rep timesRepeat:[ 
	s := s * 256 + self next
    ].
    ^ s truncated
!

nextShortMSB:msbFlag
    "return a signed short (2 bytes) from the stream.
     The receiver must support reading of binary bytes.

     The msbFlag argument controls if the integer is to be read with
     most-significant-byte-first (true) or least-first (false).
     This interface is provided to allow talking to external programs,
     where its known that the byte order is some definite one.
     If you dont care (i.e. talk to other smalltalks) or you can control the
     order, please use the corresponding xxxNet methods, which use a standard
     network byte order."

    |uval "{ Class: SmallInteger }"|

    msbFlag ifTrue:[
        "most significant first"
        uval := self next bitShift:8.
        uval := uval bitOr:(self next).
    ] ifFalse:[
        "least significant first"
        uval := self next.
        uval := uval bitOr:(self next bitShift:8).
    ].
    "change from unsigned 0..FFFF to signed -8000..7FFF"
    uval >= 16r8000 ifTrue:[
        ^ uval - 16r10000 
    ].
    ^ uval

    "Modified: 11.7.1996 / 10:07:04 / cg"
!

nextShortNet
    "return a signed short (2 bytes) in network byte order from the stream.
     The receiver must support reading of binary bytes."

    ^ self nextShortMSB:(Socket networkShortOrderIsMSB)

    "Modified: 10.1.1996 / 19:48:50 / cg"
    "Created: 10.1.1996 / 19:49:41 / cg"
!

nextUnsignedLongMSB:msbFlag
    "return an unsigned long (4 bytes) from the stream.
     The receiver must support reading of binary bytes.

     The msbFlag argument controls if the integer is to be read with
     most-significant-byte-first (true) or least-first (false).
     This interface is provided to allow talking to external programs,
     where its known that the byte order is some definite one.
     If you dont care (i.e. talk to other smalltalks) or you can control the
     order, please use the corresponding xxxNet methods, which use a standard
     network byte order."

    |val|

    msbFlag ifTrue:[
        val := self next.
        val := (val bitShift:8) bitOr:(self next).
        val := (val bitShift:8) bitOr:(self next).
        val := (val * 256) + (self next).
        ^ val
    ].
    val := self next.
    ^ (val bitShift:24)
      + (self next bitShift:16)
      + (self next bitShift:8)
      + self next

    "Modified: 11.7.1996 / 10:07:13 / cg"
!

nextUnsignedLongNet
    "return an unsigned long (4 bytes) in network byte order from the stream.
     The receiver must support reading of binary bytes."

    ^ self nextUnsignedLongMSB:(Socket networkLongOrderIsMSB)

    "Created: 10.1.1996 / 19:49:02 / cg"
    "Modified: 10.1.1996 / 19:49:50 / cg"
!

nextUnsignedShortMSB:msbFlag
    "return an unsigned short (2 bytes) from the stream.
     The receiver must support reading of binary bytes.

     The msbFlag argument controls if the integer is to be read with
     most-significant-byte-first (true) or least-first (false).
     This interface is provided to allow talking to external programs,
     where its known that the byte order is some definite one.
     If you dont care (i.e. talk to other smalltalks) or you can control the
     order, please use the corresponding xxxNet methods, which use a standard
     network byte order."

    msbFlag ifTrue:[
        ^ (self next bitShift:8) bitOr:(self next)
    ].
    ^ (self next) bitOr:(self next bitShift:8)

    "Modified: 11.7.1996 / 10:07:20 / cg"
!

nextUnsignedShortNet
    "return an unsigned short (2 bytes) in network byte order from the stream.
     The receiver must support reading of binary bytes."

    ^ self nextUnsignedShortMSB:(Socket networkShortOrderIsMSB)

    "Created: 10.1.1996 / 19:50:02 / cg"
!

nextWord
    "return the next characters which form an alphanumeric word
     (i.e. everything upTo (but excluding) the next non alphanumeric
      element)"

    ^ self nextAlphaNumericWord

    "Modified: 15.5.1996 / 17:39:32 / cg"
! !

!Stream methodsFor:'non homogenous writing'!

nextLongPut:aNumber
    "for ST-80 compatibility:
     Write the argument, aNumber as a long (four bytes). 
     The most significant byte is sent first."

    ^ self nextPutLong:aNumber MSB:true

    "Modified: 10.1.1996 / 19:38:54 / cg"
!

nextNumber:n put:v 
    "Append to the receiver the argument, v, which is a positive Integer,
     as the next n bytes. Bytes are written msb first. 
     Possibly pad with leading zeros.
     The receiver must support writing of binary bytes."

    |vlen "{ Class: SmallInteger }"
     i    "{ Class: SmallInteger }"|

    "claus: this method is central in binaryStorage -
     therefore it has been tuned a bit (and needs even more tuning)"

    v class == SmallInteger ifTrue:[  "- this is a hint to stc"
	n == 1 ifTrue:[
	    (v between:0 and:16rFF) ifTrue:[
		self nextPut:v.
		^ self
	    ].
	].
	n == 2 ifTrue:[
	    (v between:0 and:16rFFFF) ifTrue:[
		self nextPut:(v bitShift:-8).
		self nextPut:(v bitAnd:16rFF).
		^ self
	    ].
	].
	n == 3 ifTrue:[
	    (v between:0 and:16rFFFFFF) ifTrue:[
		self nextPut:((v bitShift:-16) bitAnd:16rFF).
		self nextPut:((v bitShift:-8) bitAnd:16rFF).
		self nextPut:(v bitAnd:16rFF).
		^ self
	    ].
	].
	n == 4 ifTrue:[
	    (v >= 0) ifTrue:[
		self nextPut:((v bitShift:-24) bitAnd:16rFF).
		self nextPut:((v bitShift:-16) bitAnd:16rFF).
		self nextPut:((v bitShift:-8) bitAnd:16rFF).
		self nextPut:(v bitAnd:16rFF).
		^ self
	    ].
	].
    ].

    "
     arbitrary long
    "
    n < (vlen := v digitLength) ifTrue: [
	"
	 the number is too big to be repesented in n bytes
	"
	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
    ]
!

nextPutLong:aNumber MSB:msbFlag
    "Write the argument, aNumber as a long (four bytes). 
     If msbFlag is true, data is written most-significant byte first; 
     otherwise least first. 
     Returns the receiver on ok, nil on error.
     The receiver must support writing of binary bytes.

     This interface is provided to allow talking to external programs,
     where its known that the byte order is some definite one.
     If you dont care (i.e. talk to other smalltalks) or you can control the
     order, please use the corresponding xxxNet methods, which use a standard
     network byte order."

    msbFlag ifTrue:[
        "high word first"
        self nextShortPut:(aNumber // 16r10000) MSB:true.
        ^ self nextShortPut:(aNumber \\ 16r10000) MSB:true
    ].
    "low word first"
    self nextShortPut:(aNumber \\ 16r10000) MSB:false.
    ^ self nextShortPut:(aNumber // 16r10000) MSB:false.

    "Modified: 11.7.1996 / 10:07:58 / cg"
!

nextPutLongNet:aNumber
    "Write the argument, aNumber as a long (four bytes) in the network byte order.
     Returns the receiver on ok, nil on error.
     The receiver must support writing of binary bytes."

    ^ self nextPutLong:aNumber MSB:(Socket networkLongOrderIsMSB).

    "Modified: 10.1.1996 / 19:47:10 / cg"
    "Created: 10.1.1996 / 19:50:23 / cg"
!

nextPutShort:aNumber MSB:msbFlag
    "Write the argument, aNumber as a short (two bytes). 
     If msbFlag is true, data is written most-significant byte first; 
     otherwise least first. 
     Returns the receiver on ok, nil on error.
     The receiver must support writing of binary bytes.

     This interface is provided to allow talking to external programs,
     where its known that the byte order is some definite one.
     If you dont care (i.e. talk to other smalltalks) or you can control the
     order, please use the corresponding xxxNet methods, which use a standard
     network byte order."

    |iNum "{ Class: SmallInteger }"|

    iNum := aNumber.

    msbFlag ifTrue:[
        "most significant first"
        self nextPut:(iNum bitShift:-8).
        ^ self nextPut:(iNum bitAnd:16rFF).
    ].
    "least significant first"
    self nextPut:(iNum bitAnd:16rFF).
    self nextPut:(iNum bitShift:-8).

    "Modified: 11.7.1996 / 10:08:19 / cg"
!

nextPutShortNet:aNumber
    "Write the argument, aNumber as a short (two bytes) in the network byte order.
     Returns the receiver on ok, nil on error.
     The receiver must support writing of binary bytes."

    ^ self nextPutLong:aNumber MSB:(Socket networkShortOrderIsMSB).

    "Created: 10.1.1996 / 19:50:33 / cg"
!

nextPutWord:aNumber
    "write the argument, aNumber as a signed short (two bytes);
     write msb-first for compatibility with other smalltalks.
     The receiver must support writing of binary bytes.
     I dont know if it should be named nextPutWord: or nextWordPut:;
     one of them will vanish ..."

    ^ self nextPutShort:aNumber MSB:true
!

nextShortPut:aNumber MSB:msbFlag
    "for compatibility - this will vanish"

    ^ self nextPutShort:aNumber MSB:msbFlag
!

nextWordPut:aNumber
    "for ST-80 compatibility:
     Write the argument, aNumber as a short (two bytes). 
     The most significant byte is sent first."

    ^ self nextPutShort:aNumber MSB:true

    "Modified: 10.1.1996 / 19:39:19 / cg"
! !

!Stream methodsFor:'private'!

contentsSpecies
    "this should return the class of which an instance is
     returned by the #contents method. Here, Array is returned,
     since the abstract Stream-class has no idea of the underlying 
     collection class. 
     It is redefined in some subclasses - for example, to return String."

    ^ Array

    "Modified: 15.5.1996 / 17:53:31 / cg"
! !

!Stream methodsFor:'queries'!

isBinary
    "return true, if in binary mode. Always returns false here,
     to make internalStreams protocol compatible with externalStreams."

    ^ false

    "Modified: 15.5.1996 / 17:53:51 / cg"
!

isPositionable
    "return true, if the stream supports positioning (some do not).
     Since this is an abstract class, false is returned here - just to make certain."

    ^ false

    "Modified: 15.5.1996 / 17:54:16 / cg"
!

isPrinterStream
    "return true, if this is a printerStream.
     Since this is an abstract class, false is returned here."

    ^ false

    "Modified: 15.5.1996 / 17:54:16 / cg"
    "Created: 3.6.1996 / 12:05:35 / cg"
!

isReadable
    "return true, if reading is supported by the recevier.
     This has to be redefined in concrete subclasses."

    ^ self subclassResponsibility

    "Modified: 15.5.1996 / 17:54:31 / cg"
!

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

    ^ true

    "Modified: 15.5.1996 / 17:54:48 / cg"
!

isWritable
    "return true, if writing is supported by the recevier.
     This has to be redefined in concrete subclasses."

    ^ self subclassResponsibility

    "Modified: 15.5.1996 / 17:54:54 / cg"
!

lineLength
    "return the lineLength which `looks good' when pretty printed
     text is sent to this stream.
     This has NO meaning whatsoever to regular streams;
     however, it may be used as a layout hint for prettyprinting functions
     - for compatibility with TextCollectors, which returns its views actual
       line length, and allows the prettyprinter to wrap at that position."

    ^ 80

    "Modified: 15.5.1996 / 17:57:01 / cg"
! !

!Stream methodsFor:'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 aCollection,
     which depends on the streams type - (see #contentsSpecies)."

    |answerStream 
     cnt  "{ Class: SmallInteger }" |

    answerStream := WriteStream on:(self contentsSpecies new).
    cnt := count.
    1 to:cnt do:[:index |
        answerStream nextPut:(self next)
    ].
    ^ answerStream contents

    "
     (ReadStream on:#(1 2 3 4 5)) next:3
     (ReadStream on:'hello') next:3
    "

    "Modified: 15.5.1996 / 17:57:58 / cg"
!

nextAvailable:count
    "return the next count elements of the stream as aCollection.
     If the stream reaches the end before count elements have been read,
     return what is available. (i.e. a shorter collection).
     The type of collection is speciefied in #contentsSpecies."

    |answerStream
     cnt  "{ Class: SmallInteger }"|

    answerStream := WriteStream on:(self contentsSpecies new).
    cnt := count.
    1 to:cnt do:[:index |
        self atEnd ifTrue:[
            ^ answerStream contents
        ].
        answerStream nextPut:(self next)
    ].
    ^ answerStream contents

    "
     (ReadStream on:#(1 2 3 4 5)) nextAvailable:3
     (ReadStream on:#(1 2 3 4 5)) nextAvailable:10 
     (ReadStream on:'hello') nextAvailable:3
     (ReadStream on:'hello') nextAvailable:10 
    "

    "Modified: 15.5.1996 / 17:58:42 / cg"
!

nextMatchFor:anObject
    "read an element from the receiver, return true if it was equal to
     the argument, anObject; false otherwise."

    ^ (self next = anObject)

    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     s nextMatchFor:2
    "
    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     s nextMatchFor:2.
     s nextMatchFor:2
    "

    "Modified: 15.5.1996 / 17:58:57 / cg"
!

skip:count 
    "skip count objects, return the receiver"

    |n "{ Class: SmallInteger }"|

    n := count.

    "dont know how to unread ..."
    n < 0 ifTrue:[
	^ self error:'stream is not positionable'
    ].
    n timesRepeat:self next

    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     s skip:4.
     s next
    "
!

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

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

    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     s skipFor:4.
    "

    "Modified: 15.5.1996 / 17:59:23 / cg"
!

skipThrough:anObject
    "skip all objects up-to and including anObject. Return the receiver if
     skip was successful, otherwise (i.e. if not found) return nil.
     The next read operation will return the element after anObject."

    |nextElement|

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

    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     s skipThrough:4.
     s next
    "
!

through:anObject
    "read a collection of all objects up-to anObject and return these
     elements, including anObject. 
     The next read operation will return the element after anObject.
     If anObject is not encountered, all elements up to the end are read
     and returned.
     Compare this with #upTo: which also reads up to some object
     and also positions behind it, but does not include it in the returned
     value."

    |answerStream element|

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

    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     Transcript showCR:(s through:4).  
     Transcript showCR:s next

     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     Transcript showCR:(s through:9).  
     Transcript showCR:s next

     |s|
     s := ReadStream on:'hello world'.
     Transcript showCR:(s through:Character space).
     Transcript showCR:(s upToEnd)
    "

    "Modified: 17.5.1996 / 08:51:40 / cg"
!

throughAll:aCollection
    "read & return a collection of all objects up-to and including 
     a subcollection given by aCollection.
     (i.e. read until a ``substring'' is encountered.)
     The next read operation will return the element after aCollection.
     If aCollection is not encountered, all elements up to the end are read
     and returned."

    |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:[
                ^ rslt
            ]
        ].
    ].
    ^ answerStream contents

    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     Transcript showCR:(s throughAll:#(4 4 4)).  
     Transcript showCR:s next

     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     Transcript showCR:(s throughAll:#(4 5 6)).  
     Transcript showCR:s next

     |s|
     s := ReadStream on:'hello world, this is some text'.
     Transcript showCR:(s throughAll:'world').  
     Transcript showCR:(s throughAll:'some').  
     Transcript showCR:s upToEnd.
    "

    "Modified: 15.7.1996 / 09:08:07 / cg"
!

upTo:anObject
    "read a collection of all objects up-to anObject and return these
     elements, but excluding anObject. 
     The next read operation will return the element after anObject.
     If anObject is not encountered, all elements up to the end are read
     and returned.
     Compare this with #through: which also reads up to some object
     and also positions behind it, but DOES include it in the returned
     value."

    |answerStream element|

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

    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     Transcript showCR:(s upTo:4).  
     Transcript showCR:s next

     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     Transcript showCR:(s upTo:9).  
     Transcript showCR:s next

     |s|
     s := ReadStream on:'hello world'.
     Transcript showCR:(s upTo:Character space).
     Transcript showCR:(s upToEnd)

     (ReadStream on:'12345678905') upTo:$5; upTo:$5 

     (ReadStream on:'123456') upTo:$7     

     (ReadStream on:#(1 2 3 4 5 6)) upTo:4  

     (ReadStream on:'line 1
                     line 2') upTo:Character cr  

     'Makefile' asFilename readStream upTo:Character cr;upTo:Character cr  
    "

    "Modified: 17.5.1996 / 08:51:56 / cg"
!

upToEnd
    "return a collection of the elements up-to the end.
     Return an empty collection, if the stream-end is already at the end."

    |answerStream|

    answerStream := WriteStream on:(self contentsSpecies new).
    [self atEnd] whileFalse:[
        answerStream nextPut:(self next)
    ].
    ^ answerStream contents

    "
     (ReadStream on:'1234567890') upToEnd
     ('123456' readStream) next; next; upToEnd
     ('1 23456' readStream) upTo:Character space; upToEnd 
     ('12' readStream) next; next; upToEnd  
    "

    "Modified: 15.5.1996 / 18:00:39 / cg"
! !

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

commit
    "alias for flush -- ST80 compatibility"

    ^ self flush

    "Modified: 7.5.1996 / 23:55:39 / stefan"
!

cr
    "append a carriage-return to the stream.
     This is only allowed, if the receiver supports writing."

    self nextPut:(Character cr)

    "Modified: 15.5.1996 / 18:01:21 / cg"
!

crTab
    "append a carriage-return followed by a tab to the stream.
     Same as crtab for ST/X backward compatibility.
     This is only allowed, if the receiver supports writing."

    self obsoleteMethodWarning:'use crTab'.
    self crtab

    "Modified: 15.5.1996 / 18:01:28 / cg"
!

crtab
    "append a carriage-return followed by a tab to the stream.
     This is only allowed, if the receiver supports writing."

    self crtab:1

    "Modified: 15.5.1996 / 18:01:35 / cg"
!

crtab:n
    "append a carriage-return followed by n tabs to the stream.
     This is only allowed, if the receiver supports writing."

    self nextPut:(Character cr).
    self next:n put:(Character tab)

    "Modified: 15.5.1996 / 18:01:39 / cg"
!

endEntry
    "ignored here - for compatibility with Transcript"

    ^ self
!

ff
    "append a form-feed (new-pagee) to the receiver-stream.
     This is only allowed, if the receiver supports writing."

    self nextPut:(Character ff)

    "Modified: 15.5.1996 / 18:01:47 / cg"
!

flush
    "write out all unbuffered data - ignored here, but added
     to make internalStreams protocol compatible with externalStreams"

    "Modified: 7.5.1996 / 23:54:53 / stefan"
!

next:count put:anObject
    "put the argument, anObject count times onto the receiver.
     This is only allowed, if the receiver supports writing."

    |n "{ Class: SmallInteger }"|

    n := count.
    n timesRepeat:[self nextPut:anObject].
    ^ anObject

    "
     |s|

     s := WriteStream on:#().
     s nextPut:1.
     s next:5 put:2.
     s nextPut:3.
     s contents
    "

    "Modified: 11.7.1996 / 10:00:13 / cg"
!

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
!

nextPutAll:aCollection
    "put all elements of the argument, aCollection onto the receiver.
     This is only allowed, if the receiver supports writing."

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

    "
     |s|

     s := WriteStream on:#().
     s nextPutAll:(1 to:5).
     s nextPutAll:#('one' 'two' 'three').
     s contents
    "
    "
     |s|

     s := WriteStream on:(String new).
     s nextPutAll:($a to:$f).
     s nextPutAll:'one '; 
       nextPutAll:'two ';
       nextPutAll:'three'.
     s contents
    "

    "Modified: 11.7.1996 / 10:00:21 / cg"
!

nextPutAll:aCollection startingAt:first
    "append the elements starting with index to the end
     of the argument, aCollection onto the receiver.
     This is only allowed, if the receiver supports writing."

    self nextPutAll:aCollection startingAt:first to:(aCollection size).

    "
     |s|

     s := WriteStream on:#().
     s nextPutAll:#('one' 'two' 'three' 'four' 'five') startingAt:2.
     s contents  
    "

    "Modified: 11.7.1996 / 10:00:28 / cg"
!

nextPutAll:aCollection startingAt:first to:last
    "append the elements with index from first to last
     of the argument, aCollection onto the receiver.
     This is only allowed, if the receiver supports writing."

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

    "
     |s|

     s := WriteStream on:#().
     s nextPutAll:#('one' 'two' 'three' 'four' 'five') startingAt:2 to:4.
     s contents
    "

    "Modified: 11.7.1996 / 10:00:32 / cg"
!

nextPutLine:aCollection
    "put all elements of the argument, aCollection onto the receiver,
     and append a cr. 
     This is only useful with character streams in textMode,
     and anoly allowed, if the receiver supports writing."

    self nextPutAll:aCollection.
    self cr.

    "Created: 13.12.1995 / 10:49:17 / cg"
    "Modified: 11.7.1996 / 10:00:53 / cg"
!

print:anObject
    "append a printed representation of anObject to the receiver.
     Same as 'anObject printOn:self'; Added for ST-80 compatibility."

    anObject printOn:self

    "
     |s|

     s := WriteStream on:''.
     s nextPutAll:'one ';
       print:1;
       nextPutAll:' two ';
       print:2.

     s contents
    "

    "Modified: 15.5.1996 / 18:06:06 / cg"
!

show:something
    "append a printed representation of the argument to the stream.
     This makes streams somewhat compatible to TextCollectors and
     allows you to say: 
        Smalltalk at:#Transcript put:Stdout
     or to use #show:/#showCR: with internal or external streams."

    ^ self nextPutAll:something printString

    "Modified: 15.5.1996 / 18:04:48 / cg"
!

showCR:aString
    "append a printed representation of the argument to the stream
     and append a newline character.
     This makes streams somewhat compatible to TextCollectors and
     allows you to say: 
        Smalltalk at:#Transcript put:Stdout
     or to use #show:/#showCR: with internal or external streams."

    self show:aString.
    self cr

    "Created: 18.5.1996 / 15:34:17 / cg"
    "Modified: 11.7.1996 / 10:01:27 / cg"
!

showCr:aString
    "append a printed representation of the argument to the stream
     and append a newline character.
     This is obsolete ST/X backward compatibility; use #showCR:"

    self obsoleteMethodWarning:'use #showCR:'.
    self showCR:aString.

    "Modified: 11.7.1996 / 10:01:50 / cg"
!

space
    "append a space character to the receiver.
     This is only allowed, if the receiver supports writing."

    self nextPut:(Character space)

    "Modified: 11.7.1996 / 10:02:06 / cg"
!

spaces:count
    "append count space-characters to the receiver.
     This is only allowed, if the receiver supports writing."

    self next:count put:(Character space)

    "Modified: 11.7.1996 / 10:02:10 / cg"
!

store:anObject
    "append a printed representation of anObject to the receiver,
     from which the receiver can be reconstructed (i.e. its storeString).
     Same as 'anObject storeOn:self'; Added for ST-80 compatibility."

    anObject storeOn:self

    "Modified: 15.5.1996 / 18:05:55 / cg"
!

tab
    "append a tab-character to the stream.
     This is only allowed, if the receiver supports writing."

    self nextPut:(Character tab)

    "Modified: 11.7.1996 / 10:02:20 / cg"
! !

!Stream  class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Stream.st,v 1.50 1996-07-15 07:08:44 cg Exp $'
! !
Stream initialize!