Stream.st
author Stefan Vogel <sv@exept.de>
Mon, 14 Jul 2003 12:51:53 +0200
changeset 7503 ddabde2900d2
parent 7502 a0835d8616ea
child 7505 25b0cee3b97a
permissions -rw-r--r--
Use contentsSpecies

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

"{ Package: 'stx:libbasic' }"

Object subclass:#Stream
	instanceVariableNames:'signalAtEnd'
	classVariableNames:'StreamErrorSignal PositionErrorSignal ReadErrorSignal
		WriteErrorSignal EndOfStreamSignal LineTooLongErrorSignal
		ChunkSeparator'
	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:


    [instance variables:]
	signalAtEnd             <nil | Boolean> controls behavior when a read
						is attempted past the end-of-stream
						if true, the endOfStreamSignal is
						raised.
						if false, nil is returned.
						if nil (the default), the signal
						is raised, but if there is no handler,
						nil is returned.
        
    [Class variables:]
	StreamErrorSignal       <Signal>        parent of all stream errors

	PositionErrorSignal     <Signal>        position attemted on a stream
						which does not support positioning,
						or if the position is invalid.

	ReadErrorSignal         <Signal>        raised on read errors

	WriteErrorSignal        <Signal>        raised on write errors

	EndOfStreamSignal       <Signal>        raised at end of stream if signalAtEnd
						is enabled.

    [author:]
	Claus Gittinger
"
! !

!Stream class methodsFor:'initialization'!

initSignals
"/    StreamErrorSignal := ErrorSignal newSignalMayProceed:false.
"/    StreamErrorSignal nameClass:self message:#streamErrorSignal.
    StreamErrorSignal := StreamError.
    StreamErrorSignal notifierString:'Stream error'.

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

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

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

    LineTooLongErrorSignal := QuerySignal new.
    LineTooLongErrorSignal parent:StreamErrorSignal.
    LineTooLongErrorSignal nameClass:self message:#lineTooLongErrorSignal.
    LineTooLongErrorSignal notifierString:'line too long'.

    EndOfStreamSignal := QuerySignal new.
    EndOfStreamSignal parent:StreamErrorSignal.
    EndOfStreamSignal nameClass:self message:#endOfStreamSignal.
    EndOfStreamSignal notifierString:'end of stream'.

    "Created: / 7.9.2001 / 14:15:13 / cg"
    "Modified: / 7.9.2001 / 14:15:27 / cg"
!

initialize
    ChunkSeparator := $!!.

    StreamErrorSignal isNil ifTrue:[
	self initSignals
    ]

    "Modified: / 1.11.1998 / 15:57:37 / stefan"
    "Modified: / 7.9.2001 / 14:15:51 / cg"
! !

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

incompleteNextCountSignal
    "return the signal raised if not all requested elements are returned"

    ^ IncompleteNextCountError
!

lineTooLongErrorSignal
    "return the signal raised if a line is read which is too long (>32k)"

    ^ LineTooLongErrorSignal

    "Created: / 15.10.1998 / 12:11:14 / cg"
!

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

chunkSeparator
    "return the chunk-separation character"

    ^ ChunkSeparator
! !

!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 always raise an EndOfStream exception. 
     If false, no exception is raised and nil is returned from all reading messages.
     If nil (default), the exception is raised if there is a handler; otherwise, nil is returned.
     The default is nil (for ST80 compatibility) i.e. to only raise a signal if there is a handler."

    ^ 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 to raise a signal, but return nil if
     not handled."

    signalAtEnd := aBoolean.

    "default behavior: return nil if unhandled ...
     |s|

     s := '12' readStream.
     Transcript showCR:s next.
     Transcript showCR:s next.
     Transcript showCR:s next.
     Transcript showCR:s next.
    "

    "... raise error if handled.
     |s|

     s := '12' readStream.
     Stream endOfStreamSignal handle:[:ex |
	Transcript showCR:'end reached'.
	ex return
     ] do:[
	Transcript showCR:s next.
	Transcript showCR:s next.
	Transcript showCR:s next.
	Transcript showCR:s next.
     ]
    "

    "force raise (useful for debugging):
     |s|

     s := '12' readStream.
     s signalAtEnd:true.
     Transcript showCR:s next.
     Transcript showCR:s next.
     Transcript showCR:s next.
     Transcript showCR:s next.
    "


    "force no-raise (useful for compatibility with other systems):
     |s|

     s := '12' readStream.
     s signalAtEnd:false.
     Stream endOfStreamSignal handle:[:ex |
	Transcript showCR:'end reached'.
	ex return
     ] do:[
	Transcript showCR:s next.
	Transcript showCR:s next.
	Transcript showCR:s next.
	Transcript showCR:s next.
     ]
    "

    "Modified: / 16.6.1998 / 16:04:41 / 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]
    "
!

linesDo:aBlock
    "evaluate the argument, aBlock for all lines,
     up to the end of the stream"

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

    "
     |s|
     s := '/etc/hosts' asFilename readStream.
     s linesDo:[:line | Transcript showCR:line].
     s close
    "

    "
     Filename readingFile:'/etc/hosts' 
     do:[:s |
         s linesDo:[:line | Transcript showCR:line].
     ].
    "
! !

!Stream methodsFor:'error handling'!

checkNilFileStream
    "Do nothing if this is a valid FileStream
     (i.e. the previous open operation was successful).
     Also implemented in UndefinedObject, to raise an Error there.

     This is an aid for converting from the old error reporting (returning nil)
     to the new error reporting (with real Exceptions.

     It will vanish as soon as the conversion has been done"

    ^ self
!

pastEnd
    "someone tried to read after the end of the stream.
     If signalAtEnd == true, raise a signal. If its false, return nil.
     Otherwise raise the signal, but only if handled; otherwise return nil."

    signalAtEnd == true ifTrue:[
	"/ always raise ...
	^ EndOfStreamSignal raiseRequestFrom:self
    ].
    signalAtEnd == false ifTrue:[
	"/ never raise ...
	^ nil
    ].

    "/ the default case - raise it, but return nil, if noone cares.
    Signal noHandlerSignal handle:[:ex |
	ex return
    ] do:[
	^ EndOfStreamSignal raiseRequestFrom:self
    ].
    ^ nil.

    "default behavior: return nil if unhandled ...
     |s|

     s := '12' readStream.
     Transcript showCR:s next.
     Transcript showCR:s next.
     Transcript showCR:s next.
     Transcript showCR:s next.
    "

    "... raise error if handled.
     |s|

     s := '12' readStream.
     Stream endOfStreamSignal handle:[:ex |
	Transcript showCR:'end reached'.
	ex return
     ] do:[
	Transcript showCR:s next.
	Transcript showCR:s next.
	Transcript showCR:s next.
	Transcript showCR:s next.
     ]
    "

    "force raise (useful for debugging):
     |s|

     s := '12' readStream.
     s signalAtEnd:true.
     Transcript showCR:s next.
     Transcript showCR:s next.
     Transcript showCR:s next.
     Transcript showCR:s next.
    "


    "force no-raise (useful for compatibility with other systems):
     |s|

     s := '12' readStream.
     s signalAtEnd:false.
     Stream endOfStreamSignal handle:[:ex |
	Transcript showCR:'end reached'.
	ex return
     ] do:[
	Transcript showCR:s next.
	Transcript showCR:s next.
	Transcript showCR:s next.
	Transcript showCR:s next.
     ]
    "

    "Modified: / 16.6.1998 / 16:04:13 / cg"
! !

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

blocking:aBoolean
    "set non-blocking mode.
     Ignored, since internal streams never block"

    ^ false.
!

readWait
    ^ self "/ never have to wait
!

readWaitWithTimeoutMs:millis
    ^ false "/ never have to wait
!

text
    "switch to text mode. 
     Ignored here, but added to make internalStreams protocol compatible 
     with externalStreams."

    "Modified: 15.5.1996 / 17:38:36 / cg"
    "Created: 13.9.1996 / 18:33:26 / cg"
!

writeWait
    ^ self
!

writeWaitWithTimeoutMs:millis
    ^ false "/ never have to wait
! !

!Stream methodsFor:'non homogenous reading'!

nextAvailableBytes:numBytes into:aCollection startingAt:initialIndex
    "for compatibility with ExternalStream"

    ^ self nextBytes:numBytes into:aCollection startingAt:initialIndex
!

nextBytes:count
    "read the next count bytes and return it either as a byteArray.
     If EOF is encountered while reading, a truncated byteArry or short string 
     is returned. If EOF is already reached before the first byte can be read,
     nil is returned."

    |data n|

    data := ByteArray uninitializedNew:count.
    n := self nextBytes:count into:data startingAt:1.
    n ~~ count ifTrue:[
        n == 0 ifTrue:[
            ^ nil
        ].
        data := data copyTo:n
    ].

    ^ data

    "Created: / 21.6.1997 / 11:18:57 / cg"
    "Modified: / 30.3.1998 / 18:04:58 / cg"
!

nextBytes:count into:anObject
    "read the next count bytes into an object and return the number of
     bytes read. On EOF, 0 is returned.
     If the receiver is some socket/pipe-like stream, an exception
     is raised if the connection is broken.

     The object must have non-pointer indexed instvars (i.e. it must be 
     a ByteArray, String, Float- or DoubleArray).
     If anObject is a string or byteArray and reused, this provides the
     fastest possible physical I/O (since no new objects are allocated).

     Use with care - non object oriented i/o.
     Warning: in general, you cannot use this method to pass data from other 
     architectures since it does not care for byte order or float representation."

    ^ self nextBytes:count into:anObject startingAt:1

    "Modified: 22.4.1997 / 10:41:39 / cg"
!

nextBytes:numBytes into:aCollection startingAt:initialIndex
    "return the next numBytes from the stream. If the end is
     reached before, only that many bytes are copyied into the
     collection.
     Returns the number of bytes that have been actually read.
     The receiver must support reading of binary bytes.

     Notice: this method is privided here for protocol completeness
	     with externalStreams - it is normally not used with other
	     streams."

    |n "{Class: SmallInteger }"
     dstIndex|

    dstIndex := initialIndex.
    n := 0.
    [self atEnd] whileFalse:[
	n == numBytes ifTrue:[
	    ^ n
	].

	aCollection byteAt:dstIndex put:(self nextByte).
	dstIndex := dstIndex + 1.
	n := n + 1.
    ].
    ^ n

    "
     |s n buffer|

     buffer := ByteArray new:10.

     s := ReadStream on:#[1 2 3 4 5 6 7 8 9].
     s next:3.
     n := s nextBytes:9 into:buffer startingAt:1.
     Transcript showCR:('n = %1; buffer = <%2>' bindWith:n with:buffer)
    "

    "Modified: 22.4.1997 / 10:43:08 / cg"
!

nextBytes:numBytes into:aCollection startingAt:initialIndex blockSize:blockSize
    "like nextBytes:into:startingAt:, but read in blocks of the given size.
     This leads to better beahvior when reading large chunks from a slow device,
     such as a cdrom drive (since a single unix-read is not interruptable)."

    |nR oR n|

    nR := numBytes.
    oR := initialIndex.
    [nR > 0] whileTrue:[
	n := nR.
	n > blockSize ifTrue:[n := blockSize].
	n := self nextBytes:n into:aCollection startingAt:oR.
	n == 0 ifTrue:[
	    ^ numBytes - nR
	].
	oR := oR + n.
	nR := nR - n
    ].
    ^ numBytes

    "Created: 24.4.1997 / 21:09:34 / cg"
    "Modified: 24.4.1997 / 21:19:50 / cg"
!

nextBytesInto:anObject
    "read bytes into an object, regardless of binary/text mode.
     The number of bytes to read is defined by the objects size.
     Return the number of bytes read. On EOF, 0 is returned.
     If the receiver is some socket/pipe-like stream, an exception
     is raised if the connection is broken.

     The object to read into must have non-pointer indexed instvars 
     (i.e. it must be a ByteArray, String, Float- or DoubleArray).     
     If anObject is a string or byteArray and reused, this provides the
     fastest possible physical I/O (since no new objects are allocated).

     Use with care - non object oriented i/o.
     Warning: in general, you cannot use this method to pass data from other 
     architectures since it does not care for byte order or float representation."

    ^ self nextBytes:(anObject byteSize) into:anObject startingAt:1

    " to read 100 bytes from a stream:
    
     |b aStream|

     aStream := 'smalltalk.rc' asFilename readStream.
     b := ByteArray new:100.
     aStream nextBytesInto:b.
     aStream close.
     b inspect
    "

    "
     |s aStream|
     aStream := 'smalltalk.rc' asFilename readStream.
     s := String new:100.
     aStream nextBytesInto:s.
     aStream close.
     s inspect
    "

    "Modified: 22.4.1997 / 10:42:02 / cg"
    "Created: 22.4.1997 / 10:42:26 / cg"
!

nextHyperMSB:msbFlag
    "return a signed hyper (8 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|

    uval := self nextUnsignedHyperMSB:msbFlag.
    "change from unsigned 0..FF..FF to signed -80..00..7FF..FF"

    uval >= 16r8000000000000000 ifTrue:[
      ^ uval - 16r10000000000000000 
    ].
    ^ uval

    "
     |bytes s|

     bytes := #[16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF].
     s := bytes readStream.
     Transcript showCR:(s nextHyperMSB:true) hexPrintString.
     s reset.
     Transcript showCR:(s nextHyperMSB:false) hexPrintString.

     bytes := #[16r10 16r00 16r00 16r00 16r00 16r00 16r00 16r00].
     s := bytes readStream.
     Transcript showCR:(s nextHyperMSB:true) hexPrintString.
     s reset.
     Transcript showCR:(s nextHyperMSB:false) hexPrintString.

     bytes := #[16r12 16r34 16r56 16r78 16r9a 16rbc 16rde 16rf0].
     s := bytes readStream.
     Transcript showCR:(s nextHyperMSB:true) hexPrintString.
     s reset.
     Transcript showCR:(s nextHyperMSB:false) hexPrintString.

     bytes := #[16rFe 16rdc 16rba 16r98 16r76 16r54 16r32 16r10].
     s := bytes readStream.
     Transcript showCR:(s nextHyperMSB:true) hexPrintString.
     s reset.
     Transcript showCR:(s nextHyperMSB:false) hexPrintString.
    "

    "Modified: / 14.1.1998 / 15:40:41 / 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."

    |b1 b2 b3 b4 uval "{ Class: SmallInteger }" val|

    b1 := self next.
    b2 := self next.
    b3 := self next.
    b4 := self next.

    msbFlag ifTrue:[
	"most significant first"
	uval := (b1 bitShift:8) bitOr:b2.
	uval := (uval bitShift:8) bitOr:b3.
	val := (uval bitShift:8) bitOr:b4.
    ] ifFalse:[
	"least significant first"
	uval := (b4 bitShift:8) bitOr:b3.
	uval := (uval bitShift:8) bitOr:b2.
	val := (uval bitShift:8) bitOr:b1.
    ].
    "change from unsigned 0..FFFFFFFF to signed -80000000..7FFFFFFF"

    val >= 16r80000000 ifTrue:[
      ^ val - 16r100000000 
    ].
    ^ val

    "
     |bytes s|

     bytes := #[16rFF 16rFF 16rFF 16rFF].
     s := bytes readStream.
     Transcript showCR:(s nextLongMSB:true).
     s reset.
     Transcript showCR:(s nextLongMSB:false).

     bytes := #[16r12 16r34 16r56 16r78].
     s := bytes readStream.
     Transcript showCR:(s nextLongMSB:true).
     s reset.
     Transcript showCR:(s nextLongMSB:false).

     bytes := #[16r89 16rab 16rcd 16ref].
     s := bytes readStream.
     Transcript showCR:(s nextLongMSB:true).
     s reset.
     Transcript showCR:(s nextLongMSB:false).
    "

    "Modified: / 14.1.1998 / 15:40:41 / 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:true "/ (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"
	val := (val bitShift:8) + self next.
	s := (val 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."

    |b1 b2 uval "{ Class: SmallInteger }"|

    b1 := self next.
    b2 := self next.

    msbFlag ifTrue:[
	"most significant first"
	uval := b1 bitShift:8.
	uval := uval bitOr:b2.
    ] ifFalse:[
	"least significant first"
	uval := b2 bitShift:8.
	uval := uval bitOr:b1.
    ].
    "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"
!

nextSignedByte
    "return a signed byte (-128..127) from the stream.
     The receiver must support reading of binary bytes."

    |uval "{ Class: SmallInteger }"|

    uval := self next.
    "change from unsigned 0..FF to signed -80..7F"
    uval >= 16r80 ifTrue:[
	^ uval - 16r100 
    ].
    ^ uval

    "
     #[16rFF 16r80 16r7F 16r01] readStream nextSignedByte
    "
!

nextUnsignedHyperMSB:msbFlag
    "return an unsigned hyper (8 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."

    |bytes uval t|

    bytes := self next:8.
    uval := 0.

    msbFlag ifTrue:[
	"most significant first"
	1 to:8 do:[:i |
	    t := (uval bitShift:8).
	    uval := t bitOr:(bytes at:i).
	].
    ] ifFalse:[
	"least significant first"
	8 to:1 by:-1 do:[:i |
	    t := (uval bitShift:8).
	    uval := t bitOr:(bytes at:i).
	].
    ].
    ^ uval

    "
     |bytes s|

     bytes := #[16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF].
     s := bytes readStream.
     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
     s reset.
     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.

     bytes := #[16r10 16r00 16r00 16r00 16r00 16r00 16r00 16r00].
     s := bytes readStream.
     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
     s reset.
     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.

     bytes := #[16r12 16r34 16r56 16r78 16r9a 16rbc 16rde 16rf0].
     s := bytes readStream.
     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
     s reset.
     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.

     bytes := #[16rFe 16rdc 16rba 16r98 16r76 16r54 16r32 16r10].
     s := bytes readStream.
     Transcript showCR:(s nextUnsignedHyperMSB:true) hexPrintString.
     s reset.
     Transcript showCR:(s nextUnsignedHyperMSB:false) hexPrintString.
    "

    "Modified: / 14.1.1998 / 15:40: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."

    |b1 b2 b3 b4 val|

    b1 := self next.
    b2 := self next.
    b3 := self next.
    b4 := self next.

    msbFlag ifTrue:[
	val := b1.
	val := (val bitShift:8) bitOr:b2.
	val := (val bitShift:8) bitOr:b3.
	val := (val * 256) + b4.
	^ val
    ].
    val := b4.
    val := (val bitShift:8) bitOr:b3.
    val := (val bitShift:8) bitOr:b2.
    val := (val * 256) + b1.
    ^ val

    "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:true "/ (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."

    |b1 b2|

    b1 := self next.
    b2 := self next.

    msbFlag ifTrue:[
	^ (b1 bitShift:8) bitOr:b2
    ].
    ^ (b2 bitShift:8) bitOr:b1

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

!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); 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
    ]
!

nextPutByte:aByteValue
    "write a byte. 
     Same as nextPut: here; for protocol compatibility with externalStream."

    self nextPut:aByteValue

    "Modified: 22.4.1997 / 09:05:26 / cg"
    "Created: 22.4.1997 / 10:43:55 / cg"
!

nextPutBytes:count from:anObject
    "write count bytes from an object.
     Return the number of bytes written or nil on error.
     The object must have non-pointer indexed instvars 
     (i.e. be a ByteArray, String, Float- or DoubleArray).     
     Use with care - non object oriented i/o.
     Warning: in general, you cannot use this method to pass data to other 
     architectures since it does not care for byte order or float representation."

    ^ self nextPutBytes:count from:anObject startingAt:1

    "Created: 22.4.1997 / 10:43:59 / cg"
!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     Return the number of bytes written.
     The object must have non-pointer indexed instvars 
     (i.e. be a ByteArray, String, Float- or DoubleArray).     
     Use with care - non object oriented i/o.
     This is provided for compatibility with externalStream;
     to support binary storage"

    |idx|

    idx := start.
    1 to:count do:[:i |
	self nextPutByte:(anObject byteAt:idx).
	idx := idx + 1
    ].
    ^ count

    "Created: 22.4.1997 / 10:44:09 / cg"
!

nextPutBytesFrom:anObject
    "write bytes from an object; the number of bytes is defined by
     the objects size.
     Return the number of bytes written or nil on error.
     The object must have non-pointer indexed instvars 
     (i.e. be a ByteArray, String, Float- or DoubleArray).     
     Use with care - non object oriented i/o.
     Warning: in general, you cannot use this method to pass data to other 
     architectures since it does not care for byte order or float representation."

    ^ self nextPutBytes:(anObject size) from:anObject startingAt:1

    "Created: 22.4.1997 / 10:44:18 / cg"
!

nextPutHyper:aNumber MSB:msbFlag
    "Write the argument, aNumber as a hyper (8 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:[
	1 to:8 do:[:i |
	    self nextPut:(aNumber digitByteAt:8+1-i)
	].
    ] ifFalse:[
	1 to:8 do:[:i |
	    self nextPut:(aNumber digitByteAt:i)
	].
    ].

    "
     |s bytes|

     s := #[] writeStream.
     s nextPutHyper:16r123456789abcdef0 MSB:false.
     bytes := s contents.
     s := bytes readStream.
     (s nextHyperMSB:false) hexPrintString.   
    "
    "
     |s bytes|

     s := #[] writeStream.
     s nextPutHyper:16r123456789abcdef0 MSB:true.
     bytes := s contents.
     s := bytes readStream.
     (s nextHyperMSB:true) hexPrintString.   
.
    "
    "
     |s bytes|

     s := #[] writeStream.
     s nextPutHyper:16r-8000000000000000 MSB:true.
     bytes := s contents.
     s := bytes readStream.
     (s nextHyperMSB:true) hexPrintString.    
    "
    "
     |s bytes|

     s := #[] writeStream.
     s nextPutHyper:16r-8000000000000000 MSB:false.
     bytes := s contents.
     s := bytes readStream.
     (s nextHyperMSB:false) hexPrintString.   
    "

    "Modified: / 1.11.1997 / 18:30:52 / cg"
!

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

    |hh hl lh ll b1 b2 b3 b4|

    ll := aNumber digitByteAt:1.
    lh := aNumber digitByteAt:2.
    hl := aNumber digitByteAt:3.
    hh := aNumber digitByteAt:4.
    msbFlag ifTrue:[
	"high byte first"
	b1 := hh.
	b2 := hl.
	b3 := lh.
	b4 := ll.
    ] ifFalse:[
	"low word first"
	b1 := ll.
	b2 := lh.
	b3 := hl.
	b4 := hh.
    ].
    self nextPut:b1.
    self nextPut:b2.
    self nextPut:b3.
    self nextPut:b4.

    "
     |s bytes|

     s := #[] writeStream.
     s nextPutLong:16r12345678 MSB:false.
     bytes := s contents.
     s := bytes readStream.
     (s nextLongMSB:false) hexPrintString.   
    "
    "
     |s bytes|

     s := #[] writeStream.
     s nextPutLong:16r12345678 MSB:true.
     bytes := s contents.
     s := bytes readStream.
     (s nextLongMSB:true) hexPrintString.   
.
    "
    "
     |s bytes|

     s := #[] writeStream.
     s nextPutLong:16r-80000000 MSB:true.
     bytes := s contents.
     s := bytes readStream.
     (s nextLongMSB:true) hexPrintString.   
    "
    "
     |s bytes|

     s := #[] writeStream.
     s nextPutLong:16r-80000000 MSB:false.
     bytes := s contents.
     s := bytes readStream.
     (s nextLongMSB:false) hexPrintString.   
    "

    "Modified: / 1.11.1997 / 18:30:52 / 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:true "/ (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 }" hi lo b1 b2|

    iNum := aNumber.
    lo := iNum digitByteAt:1.
    hi := iNum digitByteAt:2.
    msbFlag ifTrue:[
	"high word first"
	b1 := hi.
	b2 := lo.
    ] ifFalse:[
	"low word first"
	b1 := lo.
	b2 := hi.
    ].
    self nextPut:b1.
    self nextPut:b2.

    "
     |s|

     s := #[] writeStream.
     s nextPutShort:16r1234 MSB:false.
     s contents.  
    "
    "
     |s|

     s := #[] writeStream.
     s nextPutShort:16r1234 MSB:true.
     s contents.
    "
!

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 backward compatibility - this will vanish"

    ^ self nextPutShort:aNumber MSB:msbFlag

    "Modified: / 1.11.1997 / 18:31:05 / cg"
!

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

    ^ self contentsSpecies == ByteArray

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

lineNumber
    "return the current lineNumber if known"

    ^ nil


!

pageFormat
    "return the pageFormat - nil here.
     This has NO meaning whatsoever to regular streams;
     however, it has been added for protocol compatibility with printerStreams"

    ^ nil

    "Modified: / 15.5.1996 / 17:57:01 / cg"
    "Created: / 29.5.1998 / 16:57:48 / cg"
! !

!Stream methodsFor:'reading'!

copyToEndInto:outStream
    "read from the receiver, and write all data up to the end to another stream.
     Return the number of bytes which have been transferred"

    ^ self copyToEndInto:outStream bufferSize:1024
!

copyToEndInto:outStream bufferSize:bufferSize
    "read from the receiver, and write all data up to the end to another stream.
     Return the number of bytes which have been transferred"

    |buffer bytesWritten|

    bytesWritten := 0.
    buffer := self contentsSpecies new:bufferSize.

    [self atEnd] whileFalse:[ |readCount count|
        readCount := self nextAvailableBytes:bufferSize into:buffer startingAt:1.
        count := outStream nextPutBytes:readCount from:buffer startingAt:1.
        bytesWritten := bytesWritten + count.
    ].
    ^ bytesWritten
!

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

    cnt := count.
    answerStream := WriteStream on:(self contentsSpecies new:cnt).
    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"
!

next:count into:aWriteStream
    "put the next count elements of the stream into aWriteStream"

    |cnt  "{ Class: SmallInteger }" |

    cnt := count.
    1 to:cnt do:[:index |
        aWriteStream nextPut:self next
    ].

    "
      |writeStream|
      writeStream := #() writeStream.
      #(1 2 3 4 5) readStream next:3 into:writeStream.
      writeStream contents.

      |writeStream|
      writeStream := '' writeStream.
      'hello' readStream next:3 into:writeStream.
      writeStream contents.
    "

    "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 specified 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: / 16.6.1998 / 15:52:41 / 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"
!

nextOrNil
    "like #next, this returns the next element, if available.
     If nothing is available, this does never raise a read-beyond end signal.
     Instead, nil is returned immediately."

    self atEnd ifTrue:[^ nil].
    ^ self next
!

nextUpTo:anObject
    "read a collection of all objects up-to anObject and return these
     elements, but excluding anObject. 
     The next read operation will return anObject.
     If anObject is not encountered, all elements up to the end are read
     and returned, and the stream is positioned at the end.
     Compare this with #upTo: which positions behind anObject"

    |answerStream element|

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

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

     |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 nextUpTo:9).  
     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
    "

    "Created: 24.1.1997 / 14:08:35 / cg"
    "Modified: 24.1.1997 / 14:09:49 / cg"
!

peekOrNil
    "like #peek, this returns the next readAhead element, if available.
     However, unlike #peek, this does not raise an atEnd-query signal - even
     if handled. Instead, nil is returned immediately."

    self atEnd ifTrue:[^ nil].
    ^ self peek

    "Created: / 5.3.1998 / 02:56:49 / cg"
    "Modified: / 5.3.1998 / 13:45:07 / cg"
!

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

    "dont know how to unread ..."
    numberToSkip < 0 ifTrue:[
        PositionErrorSignal raiseRequest.
        ^ self
    ].
    numberToSkip timesRepeat:self next

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

    "Modified: / 30.7.1999 / 12:12:10 / cg"
!

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.  
    "
    "
     |s|
     s := ReadStream on:'12345678'.
     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 and leave the stream positioned at the end.
     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
    "
    "
     |s|
     s := ReadStream on:#(1 2 3 4 5 6 7 8).
     s skipThrough:4.
     s skipThrough:4.
     s next     
    "
    "
     |s|
     s := ReadStream on:'12345678'.
     s skipThrough:$4.
     s next     
    "
    "
     |s|
     s := ReadStream on:'12345678'.
     s skipThrough:$4.
     s skipThrough:$4.
     s next     
    "
    "
     |s|
     s := ReadStream on:'12345678'.
     s skipThrough:$4.
     s skipThrough:$4.
     s atEnd     
    "
!

skipThroughAll:aCollection
    "skip for and through the sequence given by the argument, aCollection;
     return nil if not found, the receiver 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."

    |buffer l first idx|

    l := aCollection size.
    first := aCollection at:1.
    [self atEnd] whileFalse:[
	buffer isNil ifTrue:[
	    buffer := self nextAvailable:l.
	].
	buffer = aCollection ifTrue:[
	    ^ self
	].
	idx := buffer indexOf:first startingAt:2.
	idx == 0 ifTrue:[
	    buffer := nil
	] ifFalse:[
	    buffer := (buffer copyFrom:idx) , (self nextAvailable:(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: 11.1.1997 / 18:55:13 / cg"
    "Modified: 11.1.1997 / 19:09:06 / cg"
!

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

throughAny:aCollection
    "read & return a collection of all objects up-to and including 
     an element contained in aCollection.
     (i.e. read until any from aCollection is encountered.)
     If no such character is encountered, all elements up to the end are read
     and returned."

    |answerStream element last|

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

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

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

    "Modified: / 11.1.1998 / 15:28:04 / 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.
     (i.e. anObject is considered a separator, which is skipped)
     Similar to #through:, but the matching object is not included in the
     returned collection.
     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

     compare the above to:
     |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 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: / 12.1.1998 / 21:58:38 / cg"
    "Modified: / 15.1.1998 / 23:28:47 / stefan"
!

upToAllExcluding:aCollection
    "read a collection of all objects up-to a element which is contained in
     aCollection and return these elements, but excluding the matching one.
     The next read operation will return the element after aCollection.
     If no such element is encountered, all elements up to the end are read
     and returned.
     See also #throughAll: which also reads up to some object
     and also positions behind it, but DOES include it in the returned
     value.
     See also #upToAll:, which returns the same, but leaves the
     read pointer before the matched subcollection."

    |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 copyWithoutLast:aCollection size
            ]
        ].
    ].
    ^ answerStream contents

    "
     |s|
     s := ReadStream on:'hello world world'.
     Transcript show:'<'; show:(s upToAllExcluding:'wo'); showCR:'>'.
     Transcript show:'<'; show:(s upToAllExcluding:'wo'); showCR:'>'.
     Transcript show:'<'; show:(s upToEnd); showCR:'>'.
    "

    "Created: / 15.6.1998 / 19:11:31 / cg"
!

upToAny:aCollectionOfObjects
    "read a collection of all objects up-to a element which is contained in
     aCollectionOfObjects and return these elements, but excluding the matching one. 
     The next read operation will return the element after anObject.
     If no such element is encountered, all elements up to the end are read
     and returned.
     Compare this with #throughAll: 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.
	(aCollectionOfObjects includes:element) ifTrue: [
	    ^ answerStream contents
	].
	answerStream nextPut:element.
    ].
    ^ answerStream contents

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

     'Makefile' asFilename readStream upToAny:($A to:$Z)  
    "

    "Created: / 30.8.1997 / 03:02:05 / cg"
    "Modified: / 11.1.1998 / 15:19:18 / 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:'reading-strings'!

nextAlphaNumericWord
    "read the next word (i.e. up to non letter-or-digit).
     Return a string containing those characters.
     Any leading non-alphaNumeric chars are skipped."

    |s c|

    [self atEnd
     or:[(c := self peek) isLetterOrDigit]] whileFalse:[
        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).
     ].
    "

    "
     |s|

     s := 'hello +++ #world ###123###abc### 1234 foo1 foo2' readStream.
     [s atEnd] whileFalse:[
        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 atEnd ifTrue:[
	^ self pastEnd
    ].
    ^ self upTo:Character cr.

    "Modified: / 19.5.1998 / 17:26:25 / 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:'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."

    <resource:#obsolete>

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

nextPutAllUntranslated:aCollection
    "for compatibility with printStreams (putAll - as-is without escapes)"

    self nextPutAll:aCollection
!

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

    self nextPutAll:aCollection.
    self cr.

    "Created: 13.12.1995 / 10:49:17 / cg"
    "Modified: 8.11.1996 / 23:53:41 / 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:"

    <resource:#obsolete>

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

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

    self next:count put:(Character tab)

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

!Stream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Stream.st,v 1.118 2003-07-14 10:51:20 stefan Exp $'
! !

Stream initialize!