ExternalStream.st
author Claus Gittinger <cg@exept.de>
Mon, 23 Oct 1995 17:55:03 +0100
changeset 443 fae13c0f1512
parent 441 41684f79f318
child 447 7e27756077fa
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1988 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.
"

ReadWriteStream subclass:#ExternalStream
       instanceVariableNames:'filePointer mode buffered binary useCRLF hitEOF didWrite lastErrorNumber'
       classVariableNames:'Lobby LastErrorNumber
			   StreamErrorSignal ReadErrorSignal WriteErrorSignal
			   InvalidReadSignal InvalidWriteSignal InvalidModeSignal
			   OpenErrorSignal StreamNotOpenSignal'
       poolDictionaries:''
       category:'Streams-External'
!

ExternalStream comment:'
COPYRIGHT (c) 1988 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/ExternalStream.st,v 1.56 1995-10-23 16:53:43 cg Exp $
'!

!ExternalStream primitiveDefinitions!

%{
#include <stdio.h>
#define _STDIO_H_INCLUDED_

#include <fcntl.h>
#define _FCNTL_H_INCLUDED_

#include <errno.h>
#define _ERRNO_H_INCLUDED_

#ifdef hpux
# define fileno(f)      ((f->__fileH << 8) | (f->__fileL))
#endif

/*
 * stdio library requires an fseek before reading whenever a file
 * is open for read/write and the last operation was a write.
 * (also vice-versa).
 * All code should use the following macro before doing reads:
 */
#define __READING__(f)                          \
    if ((_INST(didWrite) != false)              \
     && (_INST(mode) == @symbol(readwrite))) {  \
	_INST(didWrite) = false;                \
	fseek(f, 0L, 1); /* needed in stdio */  \
    }

#define __WRITING__(f)                          \
    if ((_INST(didWrite) != true)               \
     && (_INST(mode) == @symbol(readwrite))) {  \
	_INST(didWrite) = true;                 \
	fseek(f, 0L, 1); /* needed in stdio */  \
    }

/*
 * on some systems errno is a macro ... check for it here
 */
#ifndef errno
 extern errno;
#endif

%}
! !

!ExternalStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1988 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.
"
!

version
"
$Header: /cvs/stx/stx/libbasic/ExternalStream.st,v 1.56 1995-10-23 16:53:43 cg Exp $
"
!

documentation
"
    ExternalStream defines protocol common to Streams which have a file-descriptor and 
    represent some file or communicationChannel of the underlying OperatingSystem.
    ExternalStream is abstract; concrete classes are FileStream, PipeStream etc.

    ExternalStreams can be in two modes: text- (the default) and binary-mode.
    In text-mode, the elements read/written are characters; 
    while in binary-mode the basic elements are bytes which read/write as SmallIntegers 
    in the range 0..255.

    Also, the stream can be either in buffered or unbuffered mode. In buffered mode,
    data is not written until either a cr is written (in text mode) or a synchronizeOutput
    is sent (in both modes).

    The underlying OperatingSystem streams may either be closed explicitely (sending a close)
    or just forgotten - in this case, the garbage collector will eventually collect the
    object AND a close will be performed automatically (but you will NOT know when this 
    happens - so it is recommended, that you close your files when no longer needed).
    Closing is also suggested, since if smalltalk is finished (be it by purpose, or due to
    some crash) the data will not be in the file, if unclosed. 
    All streams understand the close message, so it never hurts to use it (it is defined as 
    a noop in one of the superclasses).

    Most of the methods found here redefine inherited methods for better performance,
    since I/O from/to files should be fast.

    Recovering a snapshot:
    not all streams can be restored to the state they had before - see the implementation of
    reOpen in subclasses for more information.
    For streams sitting on some communication channel (i.e. Pipes and Sockets) you should
    reestablish the stream upon image restart (make someone dependent on ObjectMemory).
    FileStreams are reopened and positioned to their offset they had at snapshot time.
    This may fail, if the file was removed or renamed - or lead to confusion
    if the contents changed in the meantime.
    Therefore, it is a good idea to reopen files and check for these things at restart time.

    Instance variables:

	filePointer     <Integer>       the unix FILE*; somehow mapped to an integer
					(notice: not the fd)
	mode            <Symbol>        #readwrite, #readonly or #writeonly
	buffered        <Boolean>       true, if buffered (i.e. collects characters - does
					not output immediately)
	binary          <Boolean>       true if in binary mode (reads bytes instead of chars)
	useCRLF         <Boolean>       true, if lines should be terminated with crlf instead
					of lf. (i.e. if file is an MSDOS-type file)
	hitEOF          <Boolean>       true, if EOF was reached

	lastErrorNumber <Integer>       the value of errno (only valid right after the error -
					updated with next i/o operation)

    Class variables:
	Lobby           <Registry>      keeps track of used ext-streams (to free up FILE*'s)

	StreamErrorSignal       <Signal> parent of all stream errors
	ReadErrorSignal         <Signal> raised on read errors
	WriteErrorSignal        <Signal> raised on write errors
	InvalidReadSignal       <Signal> raised on read from writeonly stream
	InvalidWriteSignal      <Signal> raised on write to readonly stream 
	InvalidModeSignal       <Signal> raised on text I/O with binary-stream
					 or binary I/O with text-stream
	OpenErrorSignal         <Signal> raised if open fails
	StreamNotOpenSignal     <Signal> raised on I/O with non-open stream

    Additional notes:
      This class is implemented using the underlying stdio-c library package, which
      has both advantages and disadvantages: since it is portable (posix defined), porting
      ST/X to non-Unix machines is simplified. The disadvantage is that the stdio library
      has big problems handling unbounded Streams, since the EOF handling in stdio is
      not prepared for data to arrive after EOF has been reached - time will show, if we need
      a complete rewrite for UnboundedStream ...

      Also, depending on the system, the stdio library behaves infriendly when signals
      occur while reading (for example, timer interrupts) - on real unixes (i.e. BSD) the signal
      is handled transparently - on SYS5.3 (i.e. non unixes :-) the read operation returns
      an error and errno is set to EINTR. Thats what the ugly code around all getc-calls is for.

      Notice that typical stdio's use a single errno global variable to return an error code,
      this was bad design in the stdio lib (right from the very beginning), since its much
      harder to deal with this in the presence of lightweight processes, where errno gets
      overwritten by an I/O operation done in another thread. (stdio should have been written
      to return errno as a negative number ...).
      To deal with this, the scheduler treats errno like a per-thread private variable,
      and saves/restores the errno setting when switching to another thread.
      (Notice that some thread packages do this also, but ST/X's thread implementation
      does not depend on those, but instead uses a portable private package).

      Finally, if an stdio-stream is open for both reading and writing, we have to call
      fseek whenever we are about to read after write and vice versa.
      Two macros (__READING__ and __WRITING__) have been defined to be used before every
      fread/fgetc and fwrite/putc respectively.
"
! !

!ExternalStream class methodsFor:'initialization'!

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

	OpenErrorSignal := StreamErrorSignal newSignalMayProceed:true.
	OpenErrorSignal nameClass:self message:#openErrorSignal.
	OpenErrorSignal notifierString:'open error'.

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

	InvalidReadSignal := ReadErrorSignal newSignalMayProceed:false.
	InvalidReadSignal nameClass:self message:#invalidReadSignal.
	InvalidReadSignal notifierString:'write error'.

	InvalidWriteSignal := WriteErrorSignal newSignalMayProceed:false.
	InvalidWriteSignal nameClass:self message:#invalidWriteSignal.
	InvalidWriteSignal notifierString:'write error'.

	InvalidModeSignal :=  StreamErrorSignal newSignalMayProceed:false.
	InvalidModeSignal nameClass:self message:#invalidModeSignal.
	InvalidModeSignal notifierString:'binary/text mode mismatch'.

	StreamNotOpenSignal := StreamErrorSignal newSignalMayProceed:false.
	StreamNotOpenSignal nameClass:self message:#streamNotOpenSignal.
	StreamNotOpenSignal notifierString:'stream is not open'.
    ].

    Lobby isNil ifTrue:[
	Lobby := Registry new.

	"want to get informed when returning from snapshot"
	ObjectMemory addDependent:self
    ]
!

reOpenFiles
    "reopen all files (if possible) after a snapShot load"

    Lobby do:[:aFileStream |
	aFileStream reOpen
    ]
!

update:something
    "have to reopen files when returning from snapshot"

    something == #returnFromSnapshot ifTrue:[
	self reOpenFiles
    ]
! !

!ExternalStream class methodsFor:'Signal constants'!

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

    ^ StreamErrorSignal
!

readErrorSignal
    "return the signal raised on read errors"

    ^ ReadErrorSignal
!

writeErrorSignal
    "return the signal raised on write errors"

    ^ WriteErrorSignal
!

invalidReadSignal
    "return the signal raised when reading from writeonly streams"

    ^ InvalidReadSignal
!

invalidWriteSignal
    "return the signal raised when writing to readonly streams"

    ^ InvalidWriteSignal
!

invalidModeSignal
    "return the signal raised when doing text-I/O with a binary stream
     or binary-I/O with a text stream"

    ^ InvalidModeSignal
!

streamNotOpenSignal
    "return the signal raised on I/O with closed streams"

    ^ StreamNotOpenSignal
!

openErrorSignal
    "return the signal raised when a file open failed"

    ^ OpenErrorSignal
! !

!ExternalStream class methodsFor:'instance creation'!

new
    |newStream|

    newStream := self basicNew.
    newStream text; buffered:true; useCRLF:false; clearEOF.
    ^ newStream
! !

!ExternalStream class methodsFor:'error handling'!

lastErrorNumber
    "return the errno of the last error"

    ^ LastErrorNumber

    "
     ExternalStream lastErrorNumber
    "
!

lastErrorString
    "return a message string describing the last error"

    ^ OperatingSystem errorTextForNumber:LastErrorNumber

    "
     ExternalStream lastErrorString
    "
! !

!ExternalStream methodsFor:'instance release'!

shallowCopyForFinalization
    "return a copy for finalization-registration;
     since all we need at finalization time is the fileDescriptor,
     a cheaper copy is possible."

    ^ self class basicNew setFilePointer:filePointer
!

setFilePointer:anInteger
    filePointer := anInteger
!

disposed
    "some Stream has been collected - close the file if not already done"

    self closeFile
!

shutDown
    "close the stream - added for protocol compatibility with PipeStream.
     see comment there"

    self closeFile
!

closeFile
    "low level close - may be redefined in subclasses"

%{  /* NOCONTEXT */

    OBJ fp;

    if ((fp = _INST(filePointer)) != nil) {
	_INST(filePointer) = nil;
	__BEGIN_INTERRUPTABLE__
	fclose(MKFD(fp));
	__END_INTERRUPTABLE__
    }
%}
! !

!ExternalStream methodsFor:'private'!

clearEOF
    hitEOF := false
!

reOpen
    "sent after snapin to reopen streams.
     cannot reopen here since I am abstract and have no device knowledge"

    self class name errorPrint. ': cannot reOpen stream - stream closed' errorPrintNL.
    filePointer := nil.
    Lobby unregister:self.
!

setLastError:aNumber
    lastErrorNumber := aNumber
! !

!ExternalStream methodsFor:'error handling'!

lastErrorNumber
    "return the last error"

    ^ lastErrorNumber
!

lastErrorString
    "return a message string describing the last error"

    (lastErrorNumber isNil or:[lastErrorNumber == 0]) ifTrue:[
	^ 'I/O error'
    ].
    ^ OperatingSystem errorTextForNumber:lastErrorNumber
!

errorOpen
    "report an error, that the stream is already opened"

    ^ OpenErrorSignal
	raiseRequestWith:self
	errorString:(self class name , ' is already open')
		 in:thisContext sender
!

openError
    "report an error, that the open failed"

    ^ OpenErrorSignal
	raiseRequestWith:self
	     errorString:('error on open: ' , self lastErrorString)
		      in:thisContext sender
!

errorNotOpen
    "report an error, that the stream has not been opened"

    ^ StreamNotOpenSignal
	raiseRequestWith:self
	     errorString:(self class name , ' not open')
		      in:thisContext sender
!

errorReadOnly
    "report an error, that the stream is a readOnly stream"

    ^ InvalidWriteSignal
	raiseRequestWith:self
	     errorString:(self class name , ' is readonly')
		      in:thisContext sender
!

errorWriteOnly
    "report an error, that the stream is a writeOnly stream"

    ^ InvalidReadSignal
	raiseRequestWith:self
	     errorString:(self class name , ' is writeonly')
		      in:thisContext sender
!

errorNotBinary
    "report an error, that the stream is not in binary mode"

    ^ InvalidModeSignal
	raiseRequestWith:self
	     errorString:(self class name , ' is not in binary mode')
		      in:thisContext sender
!

errorBinary
    "report an error, that the stream is in binary mode"

    ^ InvalidModeSignal
	raiseRequestWith:self
	     errorString:(self class name , ' is in binary mode')
		      in:thisContext sender
!

errorNotBuffered
    "report an error, that the stream is not in buffered mode"

    ^ StreamErrorSignal
	raiseRequestWith:self
	     errorString:(self class name , ' is unbuffered - operation not allowed')
		      in:thisContext sender
!

ioError
    "report an error, that some I/O error occured"

    ^ StreamErrorSignal
	raiseRequestWith:self
	     errorString:('I/O error: ' , self lastErrorString)
		      in:thisContext sender
!

readError
    "report an error, that some read error occured"

    ^ ReadErrorSignal
	raiseRequestWith:self
	     errorString:('read error: ' , self lastErrorString)
		      in:thisContext sender
!

writeError
    "report an error, that some write error occured"

    ^ WriteErrorSignal
	raiseRequestWith:self
	     errorString:('write error: ' , self lastErrorString)
		      in:thisContext sender
!

argumentMustBeInteger
    "report an error, that the argument must be an integer"

    ^ self error:'argument must be an integer'
!

argumentMustBeCharacter
    "report an error, that the argument must be a character"

    ^ self error:'argument must be a character'
!

argumentMustBeString
    "report an error, that the argument must be a string"

    ^ self error:'argument must be a string'
! !

!ExternalStream methodsFor:'queries'!

isExternalStream
    "return true, if the receiver is some kind of externalStream;
     true is returned here - the method redefined from Object."

    ^ true
!

isReadable 
    "return true, if this stream can be read from"

    ^ (mode ~~ #writeonly)
!

isWritable 
    "return true, if this stream can be written to"

    ^ (mode ~~ #readonly)
!

isBinary
    "return true, if the stream is in binary (as opposed to text-) mode.
     The default when created is false."

    ^ binary
! !

!ExternalStream methodsFor:'accessing'!

readonly
    "set access mode to readonly"

    mode := #readonly
!

writeonly
    "set access mode to writeonly"

    mode := #writeonly
!

readwrite
    "set access mode to readwrite"

    mode := #readwrite
!

filePointer
    "return the filePointer of the receiver -
     notice: for portability stdio is used; this means you will get
     a FILE * - not a fileDescriptor. 
     (what you really get is a corresponding integer).
     You cannot do much with the returned value 
     - except passing it to a primitive, for example."

    ^ filePointer
!

fileDescriptor
    "return the fileDescriptor of the receiver -
     notice: this one returns the underlying OSs fileDescriptor -
     this may not be available on all platforms (i.e. non unix systems)."

%{  /* NOCONTEXT */

    FILE *f;
    OBJ fp;

    if ((fp = _INST(filePointer)) != nil) {
	f = MKFD(fp);
	RETURN ( MKOBJ(fileno(f)) );
    }
%}
.
    ^ self errorNotOpen
!

buffered:aBoolean
    "turn buffering on or off - default is on"

    buffered := aBoolean
!

useCRLF:aBoolean
    "turn on or off CRLF sending (instead of LF only) - default is off"

    useCRLF := aBoolean
!

binary
    "switch to binary mode - default is text"

    binary := true
!

text
    "switch to text mode - default is text"

    binary := false
!

contentsSpecies
    "return the kind of object to be returned by sub-collection builders
     (such as upTo)"

    binary ifTrue:[
	^ ByteArray
    ].
    ^ String
!

contentsOfEntireFile
    "ST-80 compatibility"

    ^ self contents
!

contents
    "return the contents of the file from the current position up-to
     the end. If the stream is in binary mode, a ByteArray containing
     the byte values is returned.
     In text-mode, a collection of strings, each representing one line,
     is returned."

    |text l chunks sizes chunk byteCount cnt bytes offset|

    binary ifTrue:[
	"adding to a ByteArray produces quadratic time-space
	 behavior - therefore we allocate chunks, and concatenate them
	 at the end."

	chunks := OrderedCollection new.
	sizes := OrderedCollection new.
	byteCount := 0.
	[self atEnd] whileFalse:[
	    chunk := ByteArray uninitializedNew:4096.
	    cnt := self nextBytes:(chunk size) into:chunk.
	    cnt notNil ifTrue:[
		chunks add:chunk.
		sizes add:cnt.
		byteCount := byteCount + cnt
	    ]
	].

	"now, create one big ByteArray"
	bytes := ByteArray uninitializedNew:byteCount.
	offset := 1.
	1 to:chunks size do:[:index |
	    chunk := chunks at:index.
	    cnt := sizes at:index. 
	    bytes replaceFrom:offset to:(offset + cnt - 1) with:chunk.
	    offset := offset + cnt
	].
	^ bytes
    ].

    text := StringCollection new.
    [self atEnd] whileFalse:[
	l := self nextLine.
	l isNil ifTrue:[
	    ^ text
	].
	text add:l
    ].
    ^ text
! !

!ExternalStream methodsFor:'misc functions'!

open
    "open the stream
     - this must be redefined in subclass"

    ^ self subclassResponsibility
!

close
    "close the stream - tell operating system"

    filePointer isNil ifTrue:[^ self].
    Lobby unregister:self.
    self closeFile.
    filePointer := nil
!

create
    "create the stream
     - this must be redefined in subclass"

    ^ self subclassResponsibility
!

position
    "return the position
     - this must be redefined in subclass"

    ^ self subclassResponsibility
!

position:anInteger
    "set the position
     - this must be redefined in subclass"

    ^ self subclassResponsibility
!

backStep
    "step back one element -
     redefined, since position is redefined here"

    self position:(self position - 1)
!

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

    self position:"0" 1
!

setToEnd
    "redefined since it must be implemented differently"

    ^ self subclassResponsibility
!

blocking:aBoolean
    "set/clear the blocking attribute - if set (which is the default)
     a read (using next) on the receiver will block until data is available.
     If cleared, a read operation will immediately return with a value of
     nil."

    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ OperatingSystem setBlocking:aBoolean on:(self fileDescriptor)
!

async:aBoolean
    "set/clear the async attribute - if set the availability of data on 
     the receiver will trigger an ioInterrupt.
     If cleared (which is the default) no special notification is made."

    |fd|

    filePointer isNil ifTrue:[^ self errorNotOpen].
    fd := self fileDescriptor.
    aBoolean ifTrue:[
	^ OperatingSystem enableIOInterruptsOn:fd
    ].
    ^ OperatingSystem disableIOInterruptsOn:fd
!

ioctl:ioctlNumber
    "to provide a simple ioctl facility - an ioctl is performed
     on the underlying file; no arguments are passed."

%{  /* NOCONTEXT */

    FILE *f;
    int ret, ioNum, ioArg;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if ((fp = _INST(filePointer)) != nil) {
	if (__isSmallInteger(ioctlNumber)) {
	    ioNum = __intVal(ioctlNumber);
	    f = MKFD(fp);

	    __BEGIN_INTERRUPTABLE__
	    do {
		ret = ioctl(fileno(f), ioNum);
	    } while ((ret < 0) && (errno == EINTR));
	    __END_INTERRUPTABLE__

	    if (ret >= 0) {
		RETURN ( __MKSMALLINT(ret) );
	    }
	    _INST(position) = nil;
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self ioError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    "
     ioctl-number is not an integer
    "
    ^ self primitiveFailed
!

ioctl:ioctlNumber with:arg
    "to provide a simple ioctl facility - an ioctl is performed
     on the underlying file; the argument is passed as argument.
     If the argument is a number, its directly passed; if its a
     kind of ByteArray (ByteArray, String or Structure) a pointer to
     the data is passed. This allows performing most ioctls - however,
     it might be tricky to setup the buffer."

%{  /* NOCONTEXT */
    FILE *f;
    int ret, ioNum;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if ((fp = _INST(filePointer)) != nil) {
	if (__isSmallInteger(ioctlNumber) 
	 && (__isSmallInteger(arg) || __isBytes(arg))) {
	    f = MKFD(fp);
	    ioNum = __intVal(ioctlNumber);

	    __BEGIN_INTERRUPTABLE__
	    do {
		if (__isSmallInteger(arg)) {
		    ret = ioctl(fileno(f), ioNum, __intVal(arg));
		} else {
		    ret = ioctl(fileno(f), ioNum, __ByteArrayInstPtr(arg)->ba_element);
		}
	    } while ((ret < 0) && (errno == EINTR));
	    __END_INTERRUPTABLE__

	    if (ret >= 0) {
		RETURN ( __MKSMALLINT(ret) );
	    }
	    _INST(position) = nil;
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self ioError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    "
     ioctl-number is not an integer or argument is not byteArray-like
    "
    ^ self primitiveFailed
! !

!ExternalStream methodsFor:'non homogenous reading'!

nextByte
    "read the next byte and return it as an Integer; return nil on error.
     This is allowed in both text and binary modes, always returning the
     bytes binary value as an integer in 0..255."

%{  /* NOCONTEXT */

    FILE *f;
    unsigned char byte;
    int cnt;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	f = MKFD(fp);

	__BEGIN_INTERRUPTABLE__
	do {
	    if (_INST(buffered) == false) {
		cnt = read(fileno(f), &byte, 1);
	    } else {
		__READING__(f)
		cnt = fread(&byte, 1, 1, f);
	    }
	} while ((cnt < 0) && (errno == EINTR));
	__END_INTERRUPTABLE__

	if (cnt == 1) {
	    if (_INST(position) != nil)
		_INST(position) = __MKSMALLINT(__intVal(_INST(position)) + 1);
	    RETURN ( __MKSMALLINT(byte) );
	}
	if (cnt == 0) {
	    _INST(hitEOF) = true;
	    RETURN (nil);
	}
	_INST(position) = nil;
	_INST(lastErrorNumber) = __MKSMALLINT(errno);
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ self errorWriteOnly
!

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 written or nil on error. On EOF, 0 is returned.
     The object must have non-pointer indexed instvars 
     (i.e. it must 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 from other 
     architectures since it does not care for byte order or float representation."

    ^ self nextBytes:(anObject size) 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
    "
!

nextBytes:count into:anObject
    "read the next count bytes into an object and return the number of
     bytes read or nil on error. On EOF, 0 is returned.
     The object must have non-pointer indexed instvars (i.e. it must 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 from other 
     architectures since it does not care for byte order or float representation."

    ^ self nextBytes:count into:anObject startingAt:1
!

nextBytes:count into:anObject startingAt:start
    "read the next count bytes into an object and return the number of
     bytes read or 0 on EOF. Notice, that in contrast to other methods
     here, this does NOT return nil on EOF, but the actual count.
     Thus allowing read of partial blocks.

     The object must have non-pointer indexed instvars 
     (i.e. it must 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 from other 
     architectures since it does not care for byte order or float representation."

%{
    FILE *f;
    int cnt, offs;
    int objSize, nInstVars, nInstBytes;
    char *cp;
    OBJ pos, fp, oClass;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	if (__bothSmallInteger(count, start)) {
	    f = MKFD(fp);

	    oClass = __Class(anObject);
	    switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
		case BYTEARRAY:
		case WORDARRAY:
		case LONGARRAY:
		case FLOATARRAY:
		case DOUBLEARRAY:
		    break;
		default:
		    goto bad;
	    }
	    cnt = __intVal(count);
	    offs = __intVal(start) - 1;
	    nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
	    nInstBytes = OHDR_SIZE + __OBJS2BYTES__(nInstVars);
	    objSize = __Size(anObject) - nInstBytes;
	    if ((offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs))) {
		/* 
		 * mhmh - since we are interruptable, anObject may move.
		 * therefore, fetch the cp-pointer within the loop
		 */
		__READING__(f)
		__BEGIN_INTERRUPTABLE__
		do {
		    cp = (char *)__InstPtr(anObject) + nInstBytes + offs;
		    if (_INST(buffered) == false) {
			cnt = read(fileno(f), cp, cnt);
		    } else {
			if (feof(f)) {
			    cnt = 0;
			    break;
			}
			cnt = fread(cp, 1, cnt, f);
		    }
		} while ((cnt < 0) && (errno == EINTR));
		__END_INTERRUPTABLE__

		if (cnt >= 0) {
		    if (cnt == 0)
			_INST(hitEOF) = true;
		    else {
			pos = _INST(position);
			if (pos != nil)
			    _INST(position) = __MKSMALLINT(__intVal(pos) + cnt);
		    }
		    RETURN (__MKSMALLINT(cnt));
		}
		_INST(position) = nil;
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    }
	}
    }
bad: ;
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    "
     count not integer or arg not bit-like (String, ByteArray etc)
    "
    ^ self primitiveFailed
!

nextShortMSB:msbFlag
    "Read two bytes and return the value as a 16-bit signed Integer.
     If msbFlag is true, value is read with most-significant byte first, 
     otherwise least-significant byte comes first.
     A nil is returned if EOF is reached (also when EOF is hit after the first byte).
     Works in both binary and text modes."

%{  /* NOCONTEXT */
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	FILE *f;
	int first, second, err;
	short value;

	f = MKFD(fp);
	__BEGIN_INTERRUPTABLE__
	__READING__(f)

	do {
	    first = getc(f);
	} while ((first < 0) && (errno == EINTR));

	if (first != EOF) {
	    do {
		second = getc(f);
	    } while ((second < 0) && (errno == EINTR));

	    __END_INTERRUPTABLE__
	    if (second != EOF) {
		if (_INST(position) != nil) {
		    _INST(position) = __MKSMALLINT(__intVal(_INST(position)) + 2);
		}
		if (msbFlag == true) {
		    value = ((first & 0xFF) << 8) | (second & 0xFF);
		} else {
		    value = ((second & 0xFF) << 8) | (first & 0xFF);
		}
		RETURN (__MKSMALLINT(value));
	    }
	}
	__END_INTERRUPTABLE__

	if (ferror(f) && (errno != 0)) {
	    _INST(position) = nil;
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	} else {
	    _INST(hitEOF) = true;
	    RETURN (nil);
	}
    }
%}.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    ^ self readError.
!

nextUnsignedShortMSB:msbFlag
    "Read two bytes and return the value as a 16-bit unsigned Integer.
     If msbFlag is true, value is read with most-significant byte first, otherwise
     least-significant byte comes first.
     A nil is returned if EOF is reached (also when EOF is hit after the first byte).
     Works in both binary and text modes."

%{  /* NOCONTEXT */
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	FILE *f;
	int first, second;
	unsigned value;

	f = MKFD(fp);
	__BEGIN_INTERRUPTABLE__
	__READING__(f)

	do {
	    first = getc(f);
	} while ((first < 0) && (errno == EINTR));

	if (first != EOF) {
	    do {
		second = getc(f);
	    } while ((second < 0) && (errno == EINTR));

	    __END_INTERRUPTABLE__
	    if (second != EOF) {
		if (_INST(position) != nil) {
		    _INST(position) = __MKSMALLINT(__intVal(_INST(position)) + 2);
		}
		if (msbFlag == true) {
		    value = ((first & 0xFF) << 8) | (second & 0xFF);
		} else {
		    value = ((second & 0xFF) << 8) | (first & 0xFF);
		}
		RETURN (__MKSMALLINT(value));
	    }
	}
	__END_INTERRUPTABLE__

	if (ferror(f) && (errno != 0)) {
	    _INST(position) = nil;
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	} else {
	    _INST(hitEOF) = true;
	    RETURN (nil);
	}
    }
%}.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    ^ self readError.
!

nextLongMSB:msbFlag
    "Read four bytes and return the value as a 32-bit signed Integer, 
     which may be a LargeInteger.
     If msbFlag is true, value is read with most-significant byte first, 
     otherwise least-significant byte comes first.
     A nil is returned, if EOF is hit before all 4 bytes have been read.
     Works in both binary and text modes."

%{  /* NOCONTEXT */
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	FILE *f;
	int first, second, third, fourth;
	int value;

	f = MKFD(fp);
	__BEGIN_INTERRUPTABLE__
	__READING__(f)

	do {
	    first = getc(f);
	} while ((first < 0) && (errno == EINTR));
	if (first != EOF) {
	    do {
		second = getc(f);
	    } while ((second < 0) && (errno == EINTR));
	    if (second != EOF) {
		do {
		    third = getc(f);
		} while ((third < 0) && (errno == EINTR));
		if (third != EOF) {
		    do {
			fourth = getc(f);
		    } while ((fourth < 0) && (errno == EINTR));
		    if (fourth != EOF) {
			__END_INTERRUPTABLE__

			if (msbFlag == true) {
			    value = (first & 0xFF);
			    value = (value<<8) | (second & 0xFF);
			    value = (value<<8) | (third & 0xFF);
			    value = (value<<8) | (fourth & 0xFF);
			} else {
			    value = (fourth & 0xFF);
			    value = (value<<8) | (third & 0xFF);
			    value = (value<<8) | (second & 0xFF);
			    value = (value<<8) | (first & 0xFF);
			}
			if (_INST(position) != nil) {
			    _INST(position) = __MKSMALLINT(__intVal(_INST(position)) + 4);
			}
			if ((value >= _MIN_INT) && (value <= _MAX_INT)) {
			    RETURN ( __MKSMALLINT(value));
			}
			RETURN ( _MKLARGEINT(value) );
		    }
		}
	    }
	}
	__END_INTERRUPTABLE__

	if (ferror(f) && (errno != 0)) {
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	    _INST(position) = nil;
	} else {
	    _INST(hitEOF) = true;
	    RETURN (nil);
	}
    }
%}.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    ^ self readError.
!

nextUnsignedLongMSB:msbFlag
    "Read four bytes and return the value as a 32-bit unsigned Integer, which may be
     a LargeInteger.
     If msbFlag is true, value is read with most-significant byte first, otherwise
     least-significant byte comes first.
     A nil is returned, if endOfFile occurs before all 4 bytes have been read.
     Works in both binary and text modes."

%{  /* NOCONTEXT */
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	FILE *f;
	int first, second, third, fourth;
	unsigned int value;

	f = MKFD(fp);
	__BEGIN_INTERRUPTABLE__
	__READING__(f)

	do {
	    first = getc(f);
	} while ((first < 0) && (errno == EINTR));
	if (first != EOF) {
	    do {
		second = getc(f);
	    } while ((second < 0) && (errno == EINTR));
	    if (second != EOF) {
		do {
		    third = getc(f);
		} while ((third < 0) && (errno == EINTR));
		if (third != EOF) {
		    do {
			fourth = getc(f);
		    } while ((fourth < 0) && (errno == EINTR));
		    if (fourth != EOF) {
			__END_INTERRUPTABLE__

			if (msbFlag == true) {
			    value = (first & 0xFF);
			    value = (value<<8) | (second & 0xFF);
			    value = (value<<8) | (third & 0xFF);
			    value = (value<<8) | (fourth & 0xFF);
			} else {
			    value = (fourth & 0xFF);
			    value = (value<<8) | (third & 0xFF);
			    value = (value<<8) | (second & 0xFF);
			    value = (value<<8) | (first & 0xFF);
			}
			if (_INST(position) != nil) {
			    _INST(position) = __MKSMALLINT(__intVal(_INST(position)) + 4);
			}
			if (value <= _MAX_INT) {
			    RETURN ( __MKSMALLINT(value));
			}
			RETURN ( _MKULARGEINT(value) );
		    }
		}
	    }
	}
	__END_INTERRUPTABLE__

	if (ferror(f) && (errno != 0)) {
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	    _INST(position) = nil;
	} else {
	    _INST(hitEOF) = true;
	    RETURN (nil);
	}
    }
%}.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    ^ self readError.
!

nextWord
    "in text-mode:
	 read the alphaNumeric next word (i.e. up to non letter-or-digit).
	 return a string containing those characters.
     in binary-mode:
	 read two bytes (msb-first) and return the value as a 16-bit 
	 unsigned Integer (for compatibility with other smalltalks)"

    binary ifTrue:[
	^ self nextUnsignedShortMSB:true
    ].
    ^ self nextAlphaNumericWord
!

nextLong
    "Read four bytes (msb-first) and return the value as a 32-bit signed Integer.
     The returned value may be a LargeInteger.
     (msb-first for compatibility with other smalltalks)"

    ^ self nextUnsignedLongMSB:true
! !

!ExternalStream methodsFor:'non homogenous writing'!

nextPutByte:aByteValue
    "write a byte.
     Works in both binary and text modes."

%{  /* NOCONTEXT */

    FILE *f;
    char c;
    OBJ pos, fp;
    int cnt;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(readonly))) {
	if (__isSmallInteger(aByteValue)) {
	    c = __intVal(aByteValue);
	    f = MKFD(fp);
	    __BEGIN_INTERRUPTABLE__
#ifdef OLD
	    if (_INST(buffered) == false) {
		cnt = write(fileno(f), &c, 1);
	    } else 
#endif
	    {
		__WRITING__(f)
		cnt = fwrite(&c, 1, 1, f);
#ifndef OLD
		if (_INST(buffered) == false) {
		    fflush(f);
		}
#endif
	    }
	    __END_INTERRUPTABLE__

	    if (cnt == 1) {
		pos = _INST(position);
		if (pos != nil)
		    _INST(position) = __MKSMALLINT(__intVal(pos) + 1);
		RETURN (self);
	    }
	    if (cnt < 0) {
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    }
	}
    }
%}.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    ^ self writeError.
!

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
!

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
!

nextPutBytes:count from:anObject startingAt:start
    "write count bytes from an object starting at index start.
     return the number of bytes written - which could be 0.
     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."

%{  /* NOCONTEXT */
    FILE *f;
    int cnt, offs;
    int objSize, nInstVars, nInstBytes;
    char *cp;
    OBJ oClass, pos, fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(readonly))) {
	if (__bothSmallInteger(count, start)) {
	    oClass = __Class(anObject);
	    switch (__intVal(__ClassInstPtr(oClass)->c_flags) & ARRAYMASK) {
		case BYTEARRAY:
		case WORDARRAY:
		case LONGARRAY:
		case FLOATARRAY:
		case DOUBLEARRAY:
		    break;
		default:
		    goto bad;
	    }
	    cnt = __intVal(count);
	    offs = __intVal(start) - 1;
	    f = MKFD(fp);

	    nInstVars = __intVal(__ClassInstPtr(oClass)->c_ninstvars);
	    nInstBytes = OHDR_SIZE + __OBJS2BYTES__(nInstVars);
	    objSize = __Size(anObject) - nInstBytes;
	    if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
		cp = (char *)__InstPtr(anObject) + nInstBytes + offs;
		__BEGIN_INTERRUPTABLE__
#ifdef OLD
		if (_INST(buffered) == false) {
		    cnt = write(fileno(f), cp, cnt);
		} else
#endif
		{
		    __WRITING__(f)
		    cnt = fwrite(cp, 1, cnt, f);
		}
#ifndef OLD
		if (_INST(buffered) == false) {
		    fflush(f);
		}
#endif
		__END_INTERRUPTABLE__

		if (cnt >= 0) {
		    pos = _INST(position);
		    if (pos != nil)
			_INST(position) = __MKSMALLINT(__intVal(pos) + cnt);
		    RETURN ( __MKSMALLINT(cnt) );
		}
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    }
	}
    }
bad: ;
%}.
    lastErrorNumber notNil ifTrue:[^ self writeError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    ^ self primitiveFailed
!

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.
     Works in both binary and text modes."

%{  /* NOCONTEXT */

    int num;
    char bytes[2];
    FILE *f;
    int cnt;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(readonly))
     && __isSmallInteger(aNumber)) {
	num = __intVal(aNumber);
	if (msbFlag == true) {
	    bytes[0] = (num >> 8) & 0xFF;
	    bytes[1] = num & 0xFF;
	} else {
	    bytes[1] = (num >> 8) & 0xFF;
	    bytes[0] = num & 0xFF;
	}

	f = MKFD(fp);
	__BEGIN_INTERRUPTABLE__
#ifdef OLD
	if (_INST(buffered) == false) {
	    cnt = write(fileno(f), bytes, 2);
	} else 
#endif
	{
	    __WRITING__(f)
	    cnt = fwrite(bytes, 1, 2, f);
	}
#ifndef OLD
	if (_INST(buffered) == false) {
	    fflush(f);
	}
#endif
	__END_INTERRUPTABLE__

	if (cnt == 2) {
	    if (_INST(position) != nil) {
		_INST(position) = __MKSMALLINT(__intVal(_INST(position)) + 2);
	    }
	    RETURN ( self );
	}
	_INST(lastErrorNumber) = __MKSMALLINT(errno);
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self writeError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    self argumentMustBeInteger
!

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.
     Works in both binary and text modes."

%{  /* NOCONTEXT */

    int num;
    char bytes[4];
    FILE *f;
    int cnt;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(readonly))
     && __isSmallInteger(aNumber)) {
	num = __intVal(aNumber);
	if (msbFlag == true) {
	    bytes[0] = (num >> 24) & 0xFF;
	    bytes[1] = (num >> 16) & 0xFF;
	    bytes[2] = (num >> 8) & 0xFF;
	    bytes[3] = num & 0xFF;
	} else {
	    bytes[3] = (num >> 24) & 0xFF;
	    bytes[2] = (num >> 16) & 0xFF;
	    bytes[1] = (num >> 8) & 0xFF;
	    bytes[0] = num & 0xFF;
	}

	f = MKFD(fp);
	__BEGIN_INTERRUPTABLE__
#ifdef OLD
	if (_INST(buffered) == false) {
	    cnt = write(fileno(f), bytes, 4);
	} else 
#endif
	{
	    __WRITING__(f)
	    cnt = fwrite(bytes, 1, 4, f);
	}
#ifndef OLD
	if (_INST(buffered) == false) {
	    fflush(f);
	}
#endif
	__END_INTERRUPTABLE__

	if (cnt == 4) {
	    if (_INST(position) != nil) {
		_INST(position) = __MKSMALLINT(__intVal(_INST(position)) + 4);
	    }
	    RETURN ( self );
	}
	_INST(lastErrorNumber) = __MKSMALLINT(errno);
    }
%}.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    lastErrorNumber notNil ifTrue:[^ self writeError].

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

!ExternalStream methodsFor:'reading'!

peek
    "return the element to be read next without advancing read position.
     In binary mode, an integer is returned, otherwise a character.
     If there are no more elements, nil is returned.
     Not allowed in unbuffered mode."

%{  /* NOCONTEXT */

    FILE *f;
    REGISTER int c;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
#ifdef OLD
	if (_INST(buffered) == true) 
#endif
	{
	    f = MKFD(fp);

	    __BEGIN_INTERRUPTABLE__
	    __READING__(f)

	    do {
		c = getc(f);
	    } while ((c < 0) && (errno == EINTR));
	    __END_INTERRUPTABLE__

	    if (c != EOF) {
		ungetc(c, f);
		if (_INST(binary) == true) {
		    RETURN ( __MKSMALLINT(c & 0xFF) );
		}
		RETURN ( _MKCHARACTER(c & 0xFF) );
	    }
	    if (ferror(f) && (errno != 0)) {
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    } else {
		_INST(hitEOF) = true;
		RETURN ( nil );
	    }
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    buffered ifFalse:[^ self errorNotBuffered].
    ^ self errorWriteOnly
!

next
    "return the next element; advance read position.
     In binary mode, an integer is returned, otherwise a character.
     If there are no more elements, nil is returned."

%{  /* NOCONTEXT */

    FILE *f;
    int c;
    OBJ pos, fp;
    unsigned char ch;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	f = MKFD(fp);
	__BEGIN_INTERRUPTABLE__
	__READING__(f)

	do {
#ifdef OLD
	    if (_INST(buffered) == false) {
		if (read(fileno(f), &ch, 1) != 1)
		    c = EOF;
		else
		    c = ch;
	    } else 
#endif
	    {
		c = getc(f);
	    }
	} while ((c < 0) && (errno == EINTR));

	__END_INTERRUPTABLE__

	if (c != EOF) {
	    pos = _INST(position);
	    if (__isSmallInteger(pos)) {
		_INST(position) = __MKSMALLINT(__intVal(pos) + 1);
	    } else {
		_INST(position) = nil;
	    }
	    if (_INST(binary) == true) {
		RETURN ( __MKSMALLINT(c & 0xFF) );
	    }
	    RETURN ( _MKCHARACTER(c & 0xFF) );
	}
	_INST(position) = nil;
	if (ferror(f) && (errno != 0)) {
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	} else {
	    _INST(hitEOF) = true;
	    RETURN ( nil );
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    self errorWriteOnly
!

next:count
    "return the next count elements of the stream as a collection.
     Redefined to return a String or ByteArray instead of the default: Array."

    |coll|

    binary ifTrue:[
	coll := ByteArray uninitializedNew:count
    ] ifFalse:[
	coll := String new:count
    ].
    "/
    "/ Q: should we use: 
    "/    self nextBytes:count into:coll startingAt:1
    "/
    1 to:count do: [:index |
	coll at:index put:(self next)
    ].
    ^ coll
! !

!ExternalStream methodsFor:'writing'!

commit
    "write all buffered date - ignored if unbuffered"

    self synchronizeOutput
!

synchronizeOutput
    "write all buffered data - ignored if unbuffered"

%{  /* NOCONTEXT */
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if ((fp = _INST(filePointer)) != nil) {
	if (_INST(mode) != @symbol(readonly)) {
	    if (_INST(buffered) == true) {
		__BEGIN_INTERRUPTABLE__
		fflush( MKFD(fp) );
		__END_INTERRUPTABLE__
	    }
	}
    }
%}
!

nextPut:aCharacter
    "write the argument, aCharacter - return nil if failed, self if ok"

%{  /* NOCONTEXT */

    FILE *f;
    char c;
    int cnt;
    OBJ pos, fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil) 
     && (_INST(mode) != @symbol(readonly))) {
	if (_INST(binary) != true) {
	    if (__isCharacter(aCharacter)) {
		c = __intVal(__CharacterInstPtr(aCharacter)->c_asciivalue);
    doWrite:
		f = MKFD(fp);

		__BEGIN_INTERRUPTABLE__

		__WRITING__(f)

		do {
		    cnt = fwrite(&c, 1, 1, f);
		} while ((cnt != 1) && (errno == EINTR));

		if (_INST(buffered) == false) {
		    fflush(f);
		}

		__END_INTERRUPTABLE__

		if (cnt == 1) {
		    pos = _INST(position);
		    if (pos != nil) {
			_INST(position) = __MKSMALLINT(__intVal(pos) + 1);
		    }
		    RETURN ( self );
		}
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    }
	} else {
	    if (__isSmallInteger(aCharacter)) {
		c = __intVal(aCharacter);
		goto doWrite;
	    }
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self writeError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    binary ifFalse:[^ self argumentMustBeCharacter].
    ^ self argumentMustBeInteger.
!

nextPutAll:aCollection
    "write all elements of the argument, aCollection.
     Reimplemented for speed when writing strings or byteArrays.
     For others, falls back to general method in superclass."

%{  /* NOCONTEXT */

    FILE *f;
    unsigned char *cp;
    int len, cnt;
    OBJ pos, fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(readonly))) {
	cp = NULL;
	if (__isString(aCollection) || __isSymbol(aCollection)) {
	    cp = _stringVal(aCollection);
	    len = _stringSize(aCollection);
	} else {
	    if (_INST(binary) == true) {
		if (__isByteArray(aCollection)) {
		    cp = __ByteArrayInstPtr(aCollection)->ba_element;
		    len = _byteArraySize(aCollection);
		} else {
		    if (__isBytes(aCollection)) {
			int nInst;

			cp = __ByteArrayInstPtr(aCollection)->ba_element;
			len = _byteArraySize(aCollection);
			nInst = __intVal(__ClassInstPtr(__qClass(aCollection))->c_ninstvars);
			cp += __OBJS2BYTES__(nInst);
			len -= __OBJS2BYTES__(nInst);
		    }
		}
	    }
	}
	if (cp != NULL) {
	    f = MKFD(fp);

	    __BEGIN_INTERRUPTABLE__
#ifdef OLD
	    if (_INST(buffered) == false) {
		cnt = write(fileno(f), cp, len);
	    } else 
#endif
	    { 
		__WRITING__(f)
#ifdef LINUX
		errno = 0;

		/*
		 * stdio library has a bug if interrupted
		 * therefore, we go directly into write()
		 */
		if (_INST(buffered) == false) {
		    int cc, rest;

		    cnt = 0;
		    rest = len;
		    do {
			cc = write(fileno(f), cp, rest);
			if (cc >= 0) {
			    cp += cc;
			    rest -= cc;
			    cnt += cc;
			    errno = EINTR; /* kludge */
			}
		    } while ((cnt != len) && (errno == EINTR));
		} else {
		    cnt = fwrite(cp, 1, len, f);
		    if (errno == EINTR) errno = 0;
		}
#else
		errno = 0;
		do {
		    cnt = fwrite(cp, 1, len, f);
		    if (cnt != len) {
			if (cnt >= 0) {
			    /* if (errno == EINTR) */
			    {
				cp += cnt;
				len -= cnt;
# ifdef HPUX
				clearerr(f);
# endif
			    }
			}
		    }
		} while ((cnt != len) && (errno == EINTR));
#endif /* LINUX */
	    }

	    if (_INST(buffered) == false) {
		fflush(f);
	    }

	    __END_INTERRUPTABLE__
	    if (cnt == len) {
		pos = _INST(position);
		if (pos != nil) {
		    _INST(position) = __MKSMALLINT(__intVal(pos) + len);
		}
		RETURN ( self );
	    }
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self writeError].
    ^ super nextPutAll:aCollection
!

nextPutAll:aCollection startingAt:start to:stop
    "write a range of elements of the argument, aCollection.
     Reimplemented for speed when writing strings or byteArrays.
     For others, falls back to general method in superclass."

%{  /* NOCONTEXT */

    FILE *f;
    unsigned char *cp;
    int len, cnt, index1, index2;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(readonly))) {
	if (__bothSmallInteger(start, stop)) {
	    cp = NULL;
	    if (_INST(binary) != true) {
		if (__isString(aCollection) || __isSymbol(aCollection)) {
		    cp = _stringVal(aCollection);
		    len = _stringSize(aCollection);
		}
	    } else {
		if (__isByteArray(aCollection)) {
		    cp = __ByteArrayInstPtr(aCollection)->ba_element;
		    len = _byteArraySize(aCollection);
		} else {
		    if (__isBytes(aCollection)) {
			int nInst;

			cp = __ByteArrayInstPtr(aCollection)->ba_element;
			len = _byteArraySize(aCollection);
			nInst = __intVal(__ClassInstPtr(__qClass(aCollection))->c_ninstvars);
			cp += __OBJS2BYTES__(nInst);
			len -= __OBJS2BYTES__(nInst);
		    }
		}
	    }
	    if (cp != NULL) {
		f = MKFD(fp);
		index1 = __intVal(start);
		index2 = __intVal(stop);
		if ((index1 < 1) || (index2 > len) || (index2 < index1)) {
		    RETURN ( self );
		}
		if (index2 > len)
		    index2 = len;

		__BEGIN_INTERRUPTABLE__
		len = index2 - index1 + 1;

		__WRITING__(f)
                
		do {
		    cnt = fwrite(cp + index1 - 1, 1, len, f);
		    if (cnt != len) {
			if (cnt >= 0) {
			    if (errno == EINTR) {
				cp += cnt;
				len -= cnt;
			    }
			}
		    }
		} while ((cnt != len) && (errno == EINTR));

		if (_INST(buffered) == false) {
		    fflush(f);
		}

		__END_INTERRUPTABLE__
		if (cnt == len) {
		    if (_INST(position) != nil) {
			_INST(position) = __MKSMALLINT(__intVal(_INST(position)) + len);
		    }
		    RETURN ( self );
		}
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    }
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self writeError].
    ^ super nextPutAll:aCollection startingAt:start to:stop
!

cr
    "reimplemented for speed"

%{  /* NOCONTEXT */

    FILE *f;
    int cnt;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(readonly))) {
	if (_INST(binary) != true) {
	    f = MKFD(fp);

	    __BEGIN_INTERRUPTABLE__

	    __WRITING__(f)

	    do {
		cnt = fwrite("\n", 1, 1, f);
	    } while ((cnt != 1) && (errno == EINTR));

	    if (_INST(buffered) == false) {
		fflush(f);
	    }

	    __END_INTERRUPTABLE__
	    if (cnt == 1) {
		if (_INST(position) != nil) {
		    _INST(position) = __MKSMALLINT(__intVal(_INST(position)) + 1);
		}
		RETURN ( self );
	    }
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self writeError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    self errorBinary
! !

!ExternalStream methodsFor:'line reading/writing'!

nextLine
    "read the next line (characters up to newline).
     Return a string containing those characters excluding the newline.
     If the previous-to-last character is a cr, this is also removed,
     so its possible to read alien (i.e. ms-dos) text as well.
     The line must be shorter than 1K characters - otherwise its truncated."

%{  /* STACK:2000 */

    FILE *f;
    int len;
    char buffer[1024];
    char *rslt, *limit;
    int fd, ch;
    int _buffered;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	if (_INST(binary) != true) {
	    f = MKFD(fp);
	    __BEGIN_INTERRUPTABLE__
	    buffer[0] = 0;

	    _buffered = (_INST(buffered) == true);
	    if (_buffered) {
		__READING__(f);
	    } else {
		fd = fileno(f);
	    }

	    /*
	     * mhmh - the following code looks ok to me,
	     * but seems not to work for sockets
	     */
#ifdef DOES_NOT_WORK
	    if (_INST(mode) == _readwrite)
		fseek(f, 0L, 1); /* needed in stdio */
	    do {
		rslt = fgets(buffer, sizeof(buffer), f);
	    } while ((rslt == NULL) && (errno == EINTR));
#else

	    rslt = buffer;
	    limit = buffer + sizeof(buffer) - 2;

	    for (;;) {
		if (_buffered) {
#ifdef OLD
/*
		    do {
*/
			ch = getc(f);
/*
		    } while ((ch < 0) && (errno == EINTR));
*/
#else
		    errno = 0;
		    do {
			if (feof(f)) {
			    ch = EOF;
			    break;
			}
			ch = getc(f);
		    } while ((ch < 0) && (errno == EINTR));
#endif
		    if (ch == EOF) {
			if (ferror(f)) {
			    if (errno == EINTR) {
				clearerr(f);
				if (! feof(f)) {
				    continue;
				}
			    }
			    _INST(lastErrorNumber) = __MKSMALLINT(errno);
			}
			len = 0;
		    } else {
			len = 1;
			*rslt = ch;
		    }
		} else {
		    do {
			len = read(fd, rslt, 1);
		    } while ((len < 0) && (errno == EINTR));
		}
		if (len <= 0) {
		    if (rslt == buffer) {
			rslt = NULL;
		    } else {
			*rslt = '\0';
		    }
		    break;
		}
		rslt++;
		if (*(rslt-1) == '\n') {
		    *rslt = '\0';
		    break;
		}
		if (rslt >= limit) {
		    *rslt = '\0';
		    break;
		}
	    }
#endif
	    __END_INTERRUPTABLE__
	    if (rslt != NULL) {
		/*
		 * that strlen can be avoided and replaced by (rslt - buffer)
		 */
		len = strlen(buffer);
		if (_INST(position) != nil) {
		    _INST(position) = __MKSMALLINT(__intVal(_INST(position)) + len + 1);
		}
		/* remove EOL character */
		if ((len != 0) && (buffer[len-1] == '\n')) {
		    buffer[--len] = '\0';
		}
		if ((len != 0) && (buffer[len-1] == '\r')) {
		    buffer[--len] = '\0';
		}
		RETURN ( _MKSTRING(buffer COMMA_CON) );
	    }
	    if (ferror(f) && (errno != 0)) {
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    } else {
		_INST(hitEOF) = true;
		RETURN ( nil );
	    }
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    self errorBinary
!

nextPutLine:aString
    "write the characters in aString and append a newline"

%{  /* NOCONTEXT */

    FILE *f;
    int len, cnt;
    OBJ pos, fp;
    char *s;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil) 
     && (_INST(mode) != @symbol(readonly))) {
	if (_INST(binary) != true) {
	    if (__isString(aString)) {
		f = MKFD(fp);
		s = (char *) _stringVal(aString);
		len = _stringSize(aString);

		__BEGIN_INTERRUPTABLE__
#ifdef OLD
		if (_INST(buffered) == false) {
		    cnt = write(fileno(f), s, len);
		} else 
#endif
		{ 
		    __WRITING__(f)
		    cnt = fwrite(s, 1, len, f);
		}
		if (cnt == len) {
#ifdef OLD
		    if (_INST(buffered) == false) {
			cnt = write(fileno(f), "\n", 1);
		    } else 
#endif
		    { 
			cnt = fwrite("\n", 1, 1, f);
		    }
#ifndef OLD
		    if (_INST(buffered) == false) {
			if (fflush(f) == EOF) goto end;
		    }
#endif
		    if (cnt == 1) {
			pos = _INST(position);
			if (pos != nil) {
			    _INST(position) = __MKSMALLINT(__intVal(pos)+len+1);
			}
			__END_INTERRUPTABLE__
			RETURN ( self );
		    }
		}
end:
		__END_INTERRUPTABLE__
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    }
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self writeError].
    super nextPutAll:aString.
    self cr.
!

nextPutLinesFrom:aStream upToLineStartingWith:aStringOrNil
    "read from aStream up to and including a line starting with aStringOrNil
     and append it to self. 
     Can be used to copy/create large files or copy from a pipe/socket.

     If aStringOrNil is nil or not matched, copy preceeds to the end.
     (this allows for example to read a Socket and transfer the data quickly
      into a file - without creating zillions of temporary strings)"

    |srcFilePointer readError|

    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    srcFilePointer := aStream filePointer.
    srcFilePointer isNil ifTrue:[^ aStream errorNotOpen].

%{  /* STACK:2000 */

    FILE *dst, *src;
    char *matchString;
    int matchLen = 0;
    char buffer[1024];

    _INST(lastErrorNumber) = nil;
    if (__isSmallInteger(srcFilePointer)) {
	if ((aStringOrNil == nil) || __isString(aStringOrNil)) {
	    if (aStringOrNil != nil) {
		matchString = (char *) _stringVal(aStringOrNil);
		matchLen = _stringSize(aStringOrNil);
	    }
	    dst = MKFD(_INST(filePointer));
	    src = (FILE *)__intVal(srcFilePointer);
	    __BEGIN_INTERRUPTABLE__
	    errno = 0;

	    __WRITING__(dst)

	    for (;;) {
		if (fgets(buffer, sizeof(buffer)-1, src) == NULL) {
		    if (ferror(src)) {
			readError = __MKSMALLINT(errno);
			__END_INTERRUPTABLE__
			goto err;
		    }
		    break;
		}
		if (fputs(buffer, dst) == EOF) {
		    if (ferror(dst)) {
			_INST(lastErrorNumber) = __MKSMALLINT(errno);
			__END_INTERRUPTABLE__
			goto err;
		    }
		    break;
		}
#ifndef OLD
		if (_INST(buffered) == false) {
		    fflush(dst);
		}
#endif
		if (matchLen) {
		    if (strncmp(matchString, buffer, matchLen) == 0) 
			break;
		}
	    }
	    __END_INTERRUPTABLE__
	    _INST(position) = nil;
	    RETURN (self);
	}
    }
err: ;
%}.
    readError ifTrue:[
	aStream setLastErrorNumber:readError.
	^ aStream readError
    ].
    lastErrorNumber notNil ifTrue:[^ self writeError].
    buffered ifFalse:[^ self errorNotBuffered].
    "
     argument error
    "
    ^ self primitiveFailed
!

peekForLineStartingWith:aString
    "read ahead for next line starting with aString;
     return the line-string if found, or nil if EOF is encountered.
     If matched, not advance position behond that line
     i.e. nextLine will read the matched line.
     If not matched, reposition to original position for firther reading."

    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    binary ifTrue:[^ self errorBinary].

%{  /* STACK: 2000 */
    FILE *f;
    int l;
    char buffer[1024];
    char *cp;
    char *matchString;
    int  firstpos = -1, lastpos;

    _INST(lastErrorNumber) = nil;
    if (__isString(aString)) {
	matchString = (char *) _stringVal(aString);
	l = _stringSize(aString);

	f = MKFD(_INST(filePointer));
	__READING__(f)

	for (;;) {
	    lastpos = ftell(f);
	    if (firstpos == -1) firstpos = lastpos;

	    __BEGIN_INTERRUPTABLE__
	    do {
		cp = fgets(buffer, sizeof(buffer)-1, f);
	    } while ((cp == NULL) && (errno == EINTR));
	    buffer[sizeof(buffer)-1] = '\0';
	    __END_INTERRUPTABLE__

	    if (cp == NULL) {
		if (ferror(f)) {
		    _INST(lastErrorNumber) = __MKSMALLINT(errno);
		    goto err;
		} else {
		    fseek(f, firstpos, 0);
		    RETURN (nil);
		}
	    }
	    if (strncmp(cp, matchString, l) == 0) {
		fseek(f, lastpos, 0);
		break;
	    }
	}
	/* remove EOL character */
	cp = buffer;
	while (*cp && (*cp != '\n')) cp++;
	*cp = '\0';
	RETURN ( _MKSTRING(buffer COMMA_CON) );
    }
err: ;
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    ^ self argumentMustBeString
!

peekForLineStartingWithAny:aCollectionOfStrings
    "read ahead for next line starting with any of aCollectionOfStrings;
     return the index in aCollection if found, nil otherwise..
     If no match, do not change position; otherwise advance right before the
     matched line so that nextLine will return this line."

    |line startPos linePos index|

    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    binary ifTrue:[^ self errorBinary].

    startPos := self position.
    [self atEnd] whileFalse:[
	linePos := self position.
	line := self nextLine.
	line notNil ifTrue:[
	    index := 1.
	    aCollectionOfStrings do:[:prefix |
		(line startsWith:prefix) ifTrue:[
		    self position:linePos.
		    ^ index
		].
		index := index + 1
	    ]
	]
    ].
    self position:startPos.
    ^ nil
! !

!ExternalStream methodsFor:'testing'!

atEnd
    "return true, if position is at end"

%{  /* NOCONTEXT */

    FILE *f;
    OBJ fp, _true = true;
    int c;

    if (_INST(hitEOF) == _true) {
	RETURN (_true);
    }
    _INST(lastErrorNumber) = nil;
    if ((fp = _INST(filePointer)) != nil) {
	f = MKFD(fp);
#ifdef OLD
	RETURN ( feof(f) ? _true : false );
#else
	__READING__(f)

	__BEGIN_INTERRUPTABLE__
	do {
	    c = getc(f);
	} while ((c < 0) && (errno == EINTR) && (clearerr(f), 1));
	__END_INTERRUPTABLE__

	if (c != EOF) {
	    ungetc(c, f);
	    RETURN (false);
	}
	if (ferror(f) && (errno != 0)) {
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	} else {
	    _INST(hitEOF) = _true;
	    RETURN (_true);
	}
#endif
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    ^ self errorNotOpen
!

canReadWithoutBlocking
    "return true, if any data is available for reading (i.e.
     a read operation will not block the smalltalk process), false otherwise."

    |fd|

    filePointer isNil ifTrue:[^ self errorNotOpen].
    mode == #writeonly ifTrue:[^ self errorWriteOnly].

    fd := self fileDescriptor.
    ^ OperatingSystem readCheck:fd

    "
     |pipe|

     pipe := PipeStream readingFrom:'(sleep 10; echo hello)'.
     pipe canReadWithoutBlocking ifTrue:[
	 Transcript showCr:'data available'
     ] ifFalse:[
	 Transcript showCr:'no data available'
     ].
     pipe close
    "
!

canWriteWithoutBlocking
    "return true, if data can be written into the stream 
     (i.e. a write operation will not block the smalltalk process)."

    |fd|

    filePointer isNil ifTrue:[^ self errorNotOpen].
    mode == #readonly ifTrue:[^ self errorReadOnly].

    fd := self fileDescriptor.
    ^ OperatingSystem writeCheck:fd
! !

!ExternalStream methodsFor:'waiting for I/O'!

readWait
    "suspend the current process, until the receiver
     becomes ready for reading. If data is already available,
     return immediate. 
     The other threads are not affected by the wait."

    self readWaitWithTimeoutMs:nil
!

readWaitWithTimeout:timeout
    "suspend the current process, until the receiver
     becomes ready for reading or a timeout (in seconds) expired. 
     If data is already available, return immediate. 
     Return true if a timeout occured (i.e. false, if data is available).
     The other threads are not affected by the wait."

    ^ self readWaitWithTimeoutMs:timeout * 1000
!

readWaitWithTimeoutMs:timeout 
    "suspend the current process, until the receiver
     becomes ready for reading or a timeout (in milliseconds) expired. 
     If data is already available, return immediate. 
     Return true if a timeout occured (i.e. false, if data is available).
     The other threads are not affected by the wait."

    |fd inputSema hasData wasBlocked|

    filePointer isNil ifTrue:[^ self errorNotOpen].
    mode == #writeonly ifTrue:[^ self errorWriteOnly].

    fd := self fileDescriptor.
    (OperatingSystem readCheck:fd) ifTrue:[^ false].

    wasBlocked := OperatingSystem blockInterrupts.
    hasData := OperatingSystem readCheck:fd.
    hasData ifFalse:[
	inputSema := Semaphore new.
	[
	    timeout notNil ifTrue:[
		Processor signal:inputSema afterMilliseconds:timeout 
	    ].
	    Processor signal:inputSema onInput:fd.
	    Processor activeProcess state:#ioWait.
	    inputSema wait.
	    Processor disableSemaphore:inputSema.
	    hasData := OperatingSystem readCheck:fd
	] valueOnUnwindDo:[
	    Processor disableSemaphore:inputSema.
	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
	]
    ].
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ^ hasData not
!

writeWait
    "suspend the current process, until the receiver
     becomes ready for writing.
     Return immediate if the receiver is already ready. 
     The other threads are not affected by the wait."

    self writeWaitWithTimeoutMs:nil
!

writeWaitWithTimeout:timeout
    "suspend the current process, until the receiver
     becomes ready for writing or a timeout (in seconds) expired. 
     Return true if a timeout occured (i.e. false, if data is available).
     Return immediate if the receiver is already ready. 
     The other threads are not affected by the wait."

    ^ self writeWaitWithTimeoutMs:timeout * 1000
!

writeWaitWithTimeoutMs:timeout
    "suspend the current process, until the receiver
     becomes ready for writing or a timeout (in seconds) expired. 
     Return true if a timeout occured (i.e. false, if data is available).
     Return immediate if the receiver is already ready. 
     The other threads are not affected by the wait."

    |fd outputSema canWrite wasBlocked|

    filePointer isNil ifTrue:[
	^ self errorNotOpen
    ].
    mode == #readonly ifTrue:[
	^ self errorReadOnly
    ].

    fd := self fileDescriptor.
    (OperatingSystem writeCheck:fd) ifTrue:[^ false].

    wasBlocked := OperatingSystem blockInterrupts.
    canWrite := OperatingSystem writeCheck:fd.
    canWrite ifFalse:[
	outputSema := Semaphore new.
	[
	    timeout notNil ifTrue:[
		Processor signal:outputSema afterMilliseconds:timeout
	    ].
	    Processor signal:outputSema onOutput:fd.
	    Processor activeProcess state:#ioWait.
	    outputSema wait.
	    Processor disableSemaphore:outputSema.
	    canWrite := OperatingSystem writeCheck:fd
	] valueOnUnwindDo:[
	    Processor disableSemaphore:outputSema.
	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
	]
    ].
    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
    ^ canWrite not
! !
     
!ExternalStream methodsFor:'reimplemented for speed'!

peekFor:anObject
    "return true and move past next element, if next == something.
     Otherwise, stay and return false. False is also returned
     when EOF is encountered."

%{  /* NOCONTEXT */

    FILE *f;
    int c;
    int peekValue;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	if (_INST(binary) == true) {
	    if (__isSmallInteger(anObject)) {
		peekValue = __intVal(anObject) & 0xFF;
	    } else {
		goto bad;
	    }
	} else {
	    if (__isCharacter(anObject)) {
		peekValue = __intVal(_characterVal(anObject)) & 0xFF;
	    } else {
		goto bad;
	    }
	}

	f = MKFD(fp);

	if (feof(f)) {
	    _INST(hitEOF) = true;
	    RETURN (false);
	}

	__READING__(f)

	errno = 0;
	__BEGIN_INTERRUPTABLE__
	do {
	    if (feof(f)) {
		break;
	    }
	    c = getc(f);
	} while ((c < 0) && (errno == EINTR));
	__END_INTERRUPTABLE__

	if (feof(f)) {
	    _INST(hitEOF) = true;
	}

	if (c == peekValue) {
	    OBJ pos;

	    if ((pos = _INST(position)) != nil) {
		_INST(position) = __MKSMALLINT(__intVal(pos) + 1);
	    }
	    RETURN (true);
	}

	if (c != EOF) {
	    ungetc(c, f);
	    RETURN (false);
	}

	_INST(hitEOF) = true;
	if (ferror(f) && (errno != 0)) {
	    _INST(lastErrorNumber) = __MKSMALLINT(errno);
	} else {
	    RETURN (false);
	}
    }
bad: ;
%}.
    mode == #writeonly ifTrue:[^ self errorWriteOnly].
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ super peekFor:anObject
!

nextMatchFor:anObject
    "skip all objects up-to and including anObject, return anObject on success,
     nil if end-of-file is reached before. The next read operation will return
     the element after anObject."

%{  /* NOCONTEXT */

    FILE *f;
    int peekValue, c;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	if ((_INST(binary) == true) && __isSmallInteger(anObject)) {
	    peekValue = __intVal(anObject) & 0xFF;
	} else {
	    if ((_INST(binary) != true) && __isCharacter(anObject)) {
		peekValue = __intVal(_characterVal(anObject)) & 0xFF;
	    } else {
		peekValue = -1;
	    }   
	}

	if (peekValue >= 0) {
	    _INST(position) = nil;
	    f = MKFD(fp);
	    __BEGIN_INTERRUPTABLE__
	    __READING__(f)

	    for (;;) {
		do {
		    c = getc(f);
		} while ((c < 0) && (errno == EINTR));
                
		if (c == EOF) {
		    __END_INTERRUPTABLE__
		    if (ferror(f) && (errno != 0)) {
			_INST(lastErrorNumber) = __MKSMALLINT(errno);
			break;
		    }
		    _INST(hitEOF) = true;
		    RETURN (nil);
		}
		if (c == peekValue) {
		    __END_INTERRUPTABLE__
		    RETURN (anObject);
		}
	    }
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ super nextMatchFor:anObject
!

skipLine
    "read the next line (characters up to newline) skip only;
     return nil if EOF reached, self otherwise. 
     Not allowed in binary mode."

%{  /* STACK:2000 */

    FILE *f;
    char buffer[1024];
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	if (_INST(binary) != true) {
	    f = MKFD(fp);
            
	    __READING__(f)

	    __BEGIN_INTERRUPTABLE__
	    if (fgets(buffer, sizeof(buffer)-1, f) != NULL) {
		__END_INTERRUPTABLE__
		RETURN ( self );
	    }
	    __END_INTERRUPTABLE__

	    if (ferror(f) && (errno != 0)) {
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
	    } else {
		_INST(hitEOF) = true;
		RETURN ( nil );
	    }
	}
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    binary ifTrue:[^ self errorBinary].
    ^ self errorWriteOnly
!

skipThroughAll:aString
    "search & skip for the sequence given by the argument, aCollection;
     return nil if not found, self otherwise. If successfull, the next read 
     will return the character after the searchstring."

    |buffer len first|

    (aString isString and:[binary not]) ifTrue:[
	len := aString size.
	first := aString at:1.
	buffer := String new:len.
	buffer at:1 put:first.
	len := len - 1.
	[true] whileTrue:[
	    (self skipThrough:first) isNil ifTrue:[
		^ nil.
	    ].
	    (self nextBytes:len into:buffer startingAt:2) == len ifFalse:[
		^ nil
	    ].
	    buffer = aString ifTrue:[
		"
		 position back, before string
		"
		^ self
	    ].
	].
	"NOT REACHED"
    ].
    ^ super skipThroughAll:aString

    "
     |s|
     s := 'Makefile' asFilename readStream.
     s skipThroughAll:'are'.
     s next:10
    "
!

skipToAll:aString
    "skip for the sequence given by the argument, aCollection;
     return nil if not found, self otherwise. On a successful match, next read
     will return characters of aString."

    |oldPos|

    oldPos := self position.
    (self skipThroughAll:aString) isNil ifTrue:[
	"
	 restore position
	"
	self position:oldPos.
	^ nil
    ].
    "
     position before match-string
    "
    self position:(self position - aString size).
    ^ self

    "
     |s|
     s := 'Makefile' asFilename readStream.
     s skipToAll:'are'.
     s next:10
    "
!

skipThrough:aCharacter
    "skip all characters up-to and including aCharacter. Return the receiver if
     skip was successfull, otherwise (i.e. if not found) return nil.
     The next read operation will return the character after aCharacter.
     The argument, aCharacter must be character, or integer wehn in binary mode."

%{  /* NOCONTEXT */

    FILE *f;
    REGISTER int c, cSearch;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	if (_INST(binary) == true) {
	    /* searched for object must be a smallInteger */
	    if (! __isSmallInteger(aCharacter)) goto badArgument;
	    cSearch = __intVal(aCharacter);
	} else {
	    /* searched for object must be a character */
	    if (! __isCharacter(aCharacter)) goto badArgument;
	    cSearch = __intVal(_characterVal(aCharacter));
	}
	/* Q: should we just say: "not found" ? */
	if ((cSearch < 0) || (cSearch > 255)) goto badArgument;

	f = MKFD(fp);
	__READING__(f)

	__BEGIN_INTERRUPTABLE__
	while (1) {
#ifdef NOTNEEDED
	    if (feof(f)) {
		__END_INTERRUPTABLE__
		RETURN ( nil );
	    }
#endif
	    do {
		c = getc(f);
	    } while ((c < 0) && (errno == EINTR));

	    if (c == cSearch) {
		__END_INTERRUPTABLE__
		RETURN (self);
	    }
	    if (c < 0) {
		__END_INTERRUPTABLE__
		if (ferror(f) && (errno != 0)) {
		    _INST(lastErrorNumber) = __MKSMALLINT(errno);
		    break;
		} else {
		    _INST(hitEOF) = true;
		    RETURN (nil);
		}
	    }
	}
    }
badArgument: ;
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    "
     argument must be integer/character in binary mode, 
     character in text mode
    "
    ^ self error:'invalid argument'.

    "
     |s|
     s := 'Makefile' asFilename readStream.
     s skipThrough:$=.
     s next:10
    "
!

skipSeparators
    "skip all whitespace; next will return next non-white-space character
     or nil if endOfFile reached. Not allowed in binary mode.
     - reimplemented for speed"

%{  /* NOCONTEXT */

    FILE *f;
    REGISTER int c;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	if (_INST(binary) != true) {
	    f = MKFD(fp);
            
	    if (feof(f)) {
		_INST(hitEOF) = true;
		RETURN ( nil );
	    }

	    __READING__(f)

	    __BEGIN_INTERRUPTABLE__
	    while (1) {
		do {
		    if (feof(f)) {
			__END_INTERRUPTABLE__
			_INST(hitEOF) = true;
			RETURN ( nil );
		    }
		    c = getc(f);
		} while ((c < 0) && (errno == EINTR));

		switch (c) {
		    case ' ':
		    case '\t':
		    case '\n':
		    case '\r':
		    case '\b':
		    case '\014':
			break;

		    default:
			__END_INTERRUPTABLE__
			if (c < 0) {
			    _INST(hitEOF) = true;
			    if (ferror(f) && (errno != 0)) {
				_INST(lastErrorNumber) = __MKSMALLINT(errno);
				goto err;
			    }
			    RETURN ( nil );
			}
			ungetc(c, f);
			RETURN ( _MKCHARACTER(c & 0xFF) );
		}
	    }
	}
    }
err: ;
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    ^ self errorBinary.
!

skipSeparatorsExceptCR
    "skip all whitespace but no newlines;
     next will return next non-white-space character
     or nil if endOfFile reached. Not allowed in binary mode.
     - reimplemented for speed"

%{  /* NOCONTEXT */

    FILE *f;
    int c;
    OBJ fp;

    _INST(lastErrorNumber) = nil;
    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	if (_INST(binary) != true) {
	    f = MKFD(fp);
	    __READING__(f)

	    __BEGIN_INTERRUPTABLE__
	    while (1) {
                
		if (feof(f)) {
		    __END_INTERRUPTABLE__
		    _INST(hitEOF) = true;
		    RETURN ( nil );
		}

		do {
		    c = getc(f);
		} while ((c < 0) && (errno == EINTR));

		switch (c) {
		    case ' ':
		    case '\t':
		    case '\b':
			break;

		    default:
			__END_INTERRUPTABLE__
			if (c < 0) {
			    if (ferror(f) && (errno != 0)) {
				_INST(lastErrorNumber) = __MKSMALLINT(errno);
				goto err;
			    }
			    _INST(hitEOF) = true;
			    RETURN ( nil );
			}
			ungetc(c, f);
			RETURN ( _MKCHARACTER(c & 0xFF) );
		}
	    }
	}
    }
err: ;
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    ^ self errorBinary
!

nextAlphaNumericWord
    "read the next word (i.e. up to non letter-or-digit) after first
     skipping any whiteSpace.
     Return a string containing those characters.
     There is a limit of 1023 characters in the word - if longer,
     it is truncated."

%{  /* STACK: 2000 */
    FILE *f;
    int len;
    char buffer[1024];
    int ch;
    int cnt = 0;
    OBJ fp;

    if (((fp = _INST(filePointer)) != nil)
     && (_INST(mode) != @symbol(writeonly))) {
	f = MKFD(fp);
	__BEGIN_INTERRUPTABLE__
	__READING__(f)

	/*
	 * skip whiteSpace first ...
	 */
	for (;;) {
	    do {
		ch = getc(f);
	    } while ((ch < 0) && (errno == EINTR));

	    if (ch < 0) {
		if (ferror(f) && (errno != 0)) {
		    _INST(lastErrorNumber) = __MKSMALLINT(errno);
		    __END_INTERRUPTABLE__
		    goto err;
		}
		_INST(hitEOF) = true;
		break;
	    }
	    cnt++;

#ifndef NON_ASCII
	    if (ch >= ' ') break;
#endif
	    if ((ch != ' ') && (ch != '\t') && (ch != '\r')
	     && (ch != '\n') && (ch != 0x0b)) break;
	}
	ungetc(ch, f);
	cnt--;

	len = 0;
	for (;;) {
	    do {
		ch = getc(f);
	    } while ((ch < 0) && (errno == EINTR));
	    if (ch < 0) {
		if (ferror(f) && (errno != 0)) {
		    _INST(lastErrorNumber) = __MKSMALLINT(errno);
		    __END_INTERRUPTABLE__
		    goto err;
		}
		_INST(hitEOF) = true;
		break;
	    }

	    ch &= 0xFF;
	    if (! (((ch >= 'a') && (ch <= 'z')) ||
		   ((ch >= 'A') && (ch <= 'Z')) ||
		   ((ch >= '0') && (ch <= '9')))) {
		ungetc(ch, f);
		break;
	    }
	    cnt++;
	    buffer[len++] = ch;
	    if (len >= (sizeof(buffer)-1)) {
		/* emergency */
		break;
	    }
	}
	__END_INTERRUPTABLE__

	if (_INST(position) != nil) {
	    _INST(position) = __MKSMALLINT(__intVal(_INST(position)) + cnt);
	}
	buffer[len] = '\0';
	if (len != 0) {
	    RETURN ( _MKSTRING(buffer COMMA_CON) );
	}
	RETURN ( nil );
    }
err: ;
%}.
    lastErrorNumber notNil ifTrue:[^ self readError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ self errorWriteOnly
!

nextChunk
    "return the next chunk, i.e. all characters up to the next
     exclamation mark. Within the chunk, exclass have to be doubled -
     except within primitive code (this exception was added to make it easier
     to edit primitive code with external editors). This means, that other
     Smalltalks cannot always read chunks containing primitive code - but that
     doesnt really matter, since C-primitives are an ST/X feature anyway.
     Reimplemented here for more speed."

    |retVal outOfMemory|

    filePointer isNil ifTrue:[^ self errorNotOpen].
    binary ifTrue:[^ self errorBinary].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].

%{  /* STACK: 8000 */
    FILE *f;
    int done = 0;
    REGISTER int c;
    int peekC;
    static char *buffer = (char *)0;
    static fastFlag = 0;
    char fastBuffer[1024];
    char *newBuffer;
    REGISTER int index;
    int currSize;
    int inComment, inString, inPrimitive = 0;

    if (!fastFlag && buffer) {
	/*
	 * we have to be very careful with the buffer, 
	 * since in case of an interrupt while reading,
	 * the method below is left and noone frees the
	 * memory. To cleanup, we keep the ptr in a static and
	 * free it when we come here the next time.
	 */
	free(buffer);
	buffer = (char *)0;
    }

    _INST(lastErrorNumber) = nil;
    f = MKFD(_INST(filePointer));
    
    __READING__(f)

    if (feof(f)) {
	_INST(hitEOF) = true;
	RETURN (nil);
    }

    /*
     * skip spaces
     */
    while (! done) {
	__BEGIN_INTERRUPTABLE__
	do {
	    c = getc(f);
	} while ((c < 0) && (errno == EINTR));
	__END_INTERRUPTABLE__

	switch (c) {
	    case ' ':
	    case '\t':
	    case '\n':
	    case '\r':
	    case '\b':
	    case '\014':
		break;

	    case EOF:
		if (ferror(f) && (errno != 0)) {
		    _INST(lastErrorNumber) = __MKSMALLINT(errno);
		    goto err;
		}
		_INST(hitEOF) = true;
		RETURN (nil);

	    default:
		ungetc(c, f);
		done = 1;
		break;
	}
    }

    /*
     * read chunk into a buffer
     */
    buffer = fastBuffer; fastFlag = 1;
    currSize = sizeof(fastBuffer);

    index = 0;
    while (! feof(f)) {
	/* 
	 * do we have to resize the buffer ? 
	 */
	if ((index+2) >= currSize) {
	    newBuffer = (char *)malloc(currSize * 2);
	    if (! newBuffer) {
		/*
		 * mhmh - chunk seems to be very big ....
		 */
		outOfMemory = true;
		goto err;
	    }
	    bcopy(buffer, newBuffer, index);
	    if (fastFlag) {
		fastFlag = 0;
	    } else {
		free(buffer);
	    }
	    buffer = newBuffer;
	    currSize = currSize * 2;
	}

	__BEGIN_INTERRUPTABLE__
	do {
	    c = getc(f);
	} while (c < 0 && (errno == EINTR));
	__END_INTERRUPTABLE__

	if (c == '%') {
	    __BEGIN_INTERRUPTABLE__
	    do {
		peekC = getc(f);
	    } while (peekC < 0 && (errno == EINTR));
	    __END_INTERRUPTABLE__
	    ungetc(peekC, f);
	    if (peekC == '{') {
		inPrimitive++;
	    } else if (peekC == '}') {
		inPrimitive--;
	    }
	} else {
	    if (! inPrimitive) {
		if (c == '!') {
		    __BEGIN_INTERRUPTABLE__
		    do {
			c = getc(f);
		    } while (c < 0 && (errno == EINTR));
		    __END_INTERRUPTABLE__

		    if (c != '!') {
			ungetc(c, f);
			break;
		    }
		}
	    }
	}

	if (c < 0) {
	    _INST(hitEOF) = true;
	    if (ferror(f) && (errno != 0)) {
		_INST(lastErrorNumber) = __MKSMALLINT(errno);
		goto err;
	    }
	    break;
	}
	buffer[index++] = c;
    }

    buffer[index] = '\0';
    /*
     * make it a string
     */
    retVal = _MKSTRING(buffer COMMA_CON);
err:
    if (!fastFlag && buffer) {
	free(buffer);
	buffer = (char *)0;
    }
%}.
    retVal isNil ifTrue:[
	"/
	"/ arrive here with retVal==nil either on error or premature EOF
	"/ or if running out of malloc-memory
	"/
	lastErrorNumber notNil ifTrue:[^ self readError].
	outOfMemory == true ifTrue:[
	    "
	     memory allocation failed.
	     When we arrive here, there was no (unix) memory available for the
	     chunk. (seems to be too big of a chunk ...)
	     Bad luck - you should increase the swap space on your machine.
	    "
	    ^ ObjectMemory allocationFailureSignal raise.
	]
    ].
    ^ retVal
! !