ExtStream.st
author claus
Sat, 11 Dec 1993 01:46:55 +0100
changeset 12 8e03bd717355
parent 10 4f1f9a91e406
child 22 847106305963
permissions -rw-r--r--
*** empty log message ***

"
 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'
       classVariableNames:'lobby'
       poolDictionaries:''
       category:'Streams-External'
!

ExternalStream comment:'

COPYRIGHT (c) 1988 by Claus Gittinger
              All Rights Reserved

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

$Header: /cvs/stx/stx/libbasic/Attic/ExtStream.st,v 1.6 1993-12-11 00:46:55 claus Exp $

written 88 by claus
'!

%{
#include <stdio.h>
#include <fcntl.h>
#include <errno.h>
%}

!ExternalStream class methodsFor:'initialization'!

initialize
    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 contentsDo:[:aFileStream |
        aFileStream reOpen
    ]
!

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

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

!ExternalStream class methodsFor:'instance creation'!

new
    |newStream|

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

!ExternalStream methodsFor:'instance release'!

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

    self closeFile
!

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

%{  /* NOCONTEXT */

    if (_INST(filePointer) != nil) {
        int savInt;
        extern int _immediateInterrupt;

        savInt = _immediateInterrupt;
        _immediateInterrupt = 1;
        fclose(MKFD(_INST(filePointer)));
        _immediateInterrupt = savInt;
    }
%}
! !

!ExternalStream methodsFor:'private'!

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

    self class name print. ': cannot reOpen stream - stream closed' printNewline.
    filePointer := nil.
    lobby unregister:self.
! !

!ExternalStream methodsFor:'error handling'!

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

    ^ self error:(self class name , ' not open')
!

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

    ^ self error:(self class name , ' is readonly')
!

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

    ^ self error:(self class name , ' is writeonly')
!

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

    ^ self error:(self class name , ' is not in binary mode')
!

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

    ^ self error:(self class name , ' is in binary mode')
!

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

    ^ self error:(self class name , ' is unbuffered - operation not allowed')
!

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:'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)"

    ^ 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;

    if (_INST(filePointer) != nil) {
        f = MKFD(_INST(filePointer));
        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
!

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 := VariableArray new.
        sizes := VariableArray new.
        byteCount := 0.
        [self atEnd] whileFalse:[
            chunk := ByteArray uninitializedNew:4096.
            cnt := self nextBytes:(chunk size) into:chunk.
            cnt isNil ifFalse:[
                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 := Text new.
    [self atEnd] whileFalse:[
        l := self nextLine.
        l notNil ifTrue:[
            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)
!

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

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

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;
    int savInt;
    extern int _immediateInterrupt;
    extern OBJ ErrorNumber;
    extern errno;

    if (_INST(filePointer) != nil) {
        if (_isSmallInteger(ioctlNumber)) {
            ioNum = _intVal(ioctlNumber);
            f = MKFD(_INST(filePointer));
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            do {
                ret = ioctl(fileno(f), ioNum);
            } while ((ret < 0) && (errno == EINTR));
            _immediateInterrupt = savInt;
            if (ret >= 0) {
                RETURN ( _MKSMALLINT(ret) );
            }
            ErrorNumber = _MKSMALLINT(errno);
            RETURN ( nil );
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    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."

    |isStructure|

    isStructure := arg isKindOf:ByteArray.
%{
    FILE *f;
    int ret, ioNum, savInt;
    extern int _immediateInterrupt;
    extern OBJ ErrorNumber;
    extern errno;

    if (_INST(filePointer) != nil) {
        if (_isSmallInteger(ioctlNumber) 
         && (_isSmallInteger(arg) || (isStructure == true))) {
            f = MKFD(_INST(filePointer));
            ioNum = _intVal(ioctlNumber);
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            do {
                if (isStructure == true) {
                    ret = ioctl(fileno(f), ioNum, _ByteArrayInstPtr(arg)->ba_element);
                } else {
                    ret = ioctl(fileno(f), ioNum, _intVal(arg));
                }
            } while ((ret < 0) && (errno == EINTR));
            _immediateInterrupt = savInt;
            if (ret >= 0) {
                RETURN ( _MKSMALLINT(ret) );
            }
            ErrorNumber = _MKSMALLINT(errno);
            RETURN ( nil );
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    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."

%{  /* NOCONTEXT */

    FILE *f;
    unsigned char byte;
    int cnt, savInt;
    extern OBJ ErrorNumber;
    extern errno;
    extern int _immediateInterrupt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
        f = MKFD(_INST(filePointer));
        savInt = _immediateInterrupt;
        _immediateInterrupt = 1;
        do {
            if (_INST(buffered) == false) {
                cnt = read(fileno(f), &byte, 1);
            } else {
                if (_INST(mode) == _readwrite)
                    fseek(f, 0L, 1); /* needed in stdio */
                cnt = fread(&byte, 1, 1, f);
            }
        } while ((cnt < 0) && (errno == EINTR));
        _immediateInterrupt = savInt;
        if (cnt == 1) {
            if (_INST(position) != nil)
                _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 1);
            RETURN ( _MKSMALLINT(byte) );
        }
        if (cnt < 0) {
            ErrorNumber = _MKSMALLINT(errno);
        }
        RETURN ( nil );
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    self errorWriteOnly
!

nextBytes:count into:anObject
    "read the next count bytes into an object and return the number of
     bytes read or nil on error.
     Use with care - non object oriented i/o.
     You can create bad crashes with this method."

    ^ 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 nil on error.
     Use with care - non object oriented i/o. 
     You can create bad crashes with this method."

%{  /* NOCONTEXT */

    FILE *f;
    int cnt, offs;
    int objSize, savInt;
    char *cp;
    extern OBJ ErrorNumber;
    extern errno;
    OBJ pos;
    extern int _immediateInterrupt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
        if (_isSmallInteger(count) && _isSmallInteger(start)) {
            cnt = _intVal(count);
            offs = _intVal(start) - 1;
            f = MKFD(_INST(filePointer));
            objSize = _Size(anObject) - OHDR_SIZE;
            if ((offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs))) {
                cp = (char *)_InstPtr(anObject) + OHDR_SIZE + offs;
                savInt = _immediateInterrupt;
                _immediateInterrupt = 1;
                do {
                    if (_INST(buffered) == false) {
                        cnt = read(fileno(f), cp, cnt);
                    } else {
                        if (_INST(mode) == _readwrite)
                            fseek(f, 0L, 1); /* needed in stdio */
                        cnt = fread(cp, 1, cnt, f);
                    }
                } while ((cnt < 0) && (errno == EINTR));
                _immediateInterrupt = savInt;
                if (cnt >= 0) {
                    pos = _INST(position);
                    if (pos != nil)
                        _INST(position) = _MKSMALLINT(_intVal(pos) + cnt);
                    RETURN ( _MKSMALLINT(cnt) );
                }
                ErrorNumber = _MKSMALLINT(errno);
                RETURN ( nil );
            }
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    self primitiveFailed
!

nextWord
    "in text-mode:
         read the 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)"

%{  /* NOCONTEXT */
    extern int _immediateInterrupt;
    int savInt;

    if (_INST(binary) == true) {
        if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
            FILE *f;
            unsigned char hi, low;
            int cnt;

            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            f = MKFD(_INST(filePointer));
            do {
                if (_INST(buffered) == false) {
                    cnt = read(fileno(f), &hi, 1);
                } else {
                    if (_INST(mode) == _readwrite)
                        fseek(f, 0L, 1); /* needed in stdio */
                    cnt = fread(&hi, 1, 1, f);
                }
            } while ((cnt < 0) && (errno == EINTR));

            if (cnt < 0) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            do {
                if (_INST(buffered) == false) {
                    cnt = read(fileno(f), &low, 1);
                } else {
                    if (_INST(mode) == _readwrite)
                        fseek(f, 0L, 1); /* needed in stdio */
                    cnt = fread(&low, 1, 1, f);
                }
            } while ((cnt < 0) && (errno == EINTR));

            _immediateInterrupt = savInt;
            if (cnt < 0) {
                if (_INST(position) != nil) {
                    _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 1);
                }
                RETURN ( _MKSMALLINT(hi & 0xFF) );
            }
            if (_INST(position) != nil) {
                _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 2);
            }
            RETURN ( _MKSMALLINT(((hi & 0xFF)<<8) | (low & 0xFF)) );
        }
    }
%}
.
%{  /* STACK: 2000 */
    FILE *f;
    int len;
    char buffer[1024];
    int ch, savInt;
    int cnt = 0;
    extern int _immediateInterrupt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
        f = MKFD(_INST(filePointer));
        savInt = _immediateInterrupt;
        _immediateInterrupt = 1;

        /* text-mode */
        for (;;) {
            ch = getc(f);
            cnt++;

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

        len = 0;
        for (;;) {
            ch = getc(f);
            if (ch == EOF)
                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;
            }
        }
        _immediateInterrupt = savInt;

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

nextShortMSB:msbFlag
    "in binary-mode only:
     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 also returned, if endOfFile occurs after the first byte."

%{  /* NOCONTEXT */
    int savInt;
    extern int _immediateInterrupt;

    if (_INST(binary) == true) {
        if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
            FILE *f;
            int first, second;
            short value;

            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;

            f = MKFD(_INST(filePointer));
            first = getc(f);
            if (first == EOF) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            second = getc(f);
            _immediateInterrupt = savInt;

            if (second == EOF) {
                RETURN ( nil );
            }
            if (_INST(position) != nil) {
                _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 2);
            }
            if (msbFlag == true) {
                RETURN ( _MKSMALLINT(((first & 0xFF)<<8) | (second & 0xFF)) );
            }
            RETURN ( _MKSMALLINT(((second & 0xFF)<<8) | (first & 0xFF)) );
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    binary ifFalse:[^ self errorNotBinary].
    self primitiveFailed
!

nextUnsignedShortMSB:msbFlag
    "in binary-mode only:
     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 also returned, if endOfFile occurs after the first byte."

%{  /* NOCONTEXT */
    int savInt;
    extern int _immediateInterrupt;

    if (_INST(binary) == true) {
        if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
            FILE *f;
            int first, second;

            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            f = MKFD(_INST(filePointer));
            first = getc(f);
            if (first == EOF) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            second = getc(f);
            _immediateInterrupt = savInt;

            if (second == EOF) {
                RETURN ( nil );
            }
            if (_INST(position) != nil) {
                _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 2);
            }
            if (msbFlag == true) {
                RETURN ( _MKSMALLINT(((first & 0xFF)<<8) | (second & 0xFF)) );
            }
            RETURN ( _MKSMALLINT(((second & 0xFF)<<8) | (first & 0xFF)) );
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    binary ifFalse:[^ self errorNotBinary].
    self primitiveFailed
!

nextLongMSB:msbFlag
    "in binary-mode only:
     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 endOfFile occurs before all 4 bytes have been read."

%{  /* NOCONTEXT */
    int savInt;
    extern int _immediateInterrupt;

    if (_INST(binary) == true) {
        if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
            FILE *f;
            int first, second, third, fourth;
            int value;

            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            f = MKFD(_INST(filePointer));
            first = getc(f);
            if (first == EOF) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            second = getc(f);
            if (second == EOF) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            third = getc(f);
            if (third == EOF) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            fourth = getc(f);
            _immediateInterrupt = savInt;
            if (fourth == EOF) {
                RETURN ( nil );
            }
            if (_INST(position) != nil) {
                _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 4);
            }
            if (msbFlag == true) {
                value = ((first & 0xFF) << 24)
                        | ((second & 0xFF) << 16)
                        | ((third & 0xFF) << 8)
                        | (fourth & 0xFF);
            } else {
                value = ((fourth & 0xFF) << 24)
                        | ((third & 0xFF) << 16)
                        | ((second & 0xFF) << 8)
                        | (first & 0xFF);
            }
            if ((value >= _MIN_INT) && (value <= _MAX_INT)) {
                RETURN ( _MKSMALLINT(value));
            }
            RETURN ( _makeLarge(value) );
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    binary ifFalse:[^ self errorNotBinary].
    self primitiveFailed
!

nextUnsignedLongMSB:msbFlag
    "in binary-mode only:
     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."

%{  /* NOCONTEXT */
    int savInt;
    extern int _immediateInterrupt;
    extern OBJ _makeULarge();

    if (_INST(binary) == true) {
        if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
            FILE *f;
            int first, second, third, fourth;
            unsigned int value;

            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            f = MKFD(_INST(filePointer));
            first = getc(f);
            if (first == EOF) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            second = getc(f);
            if (second == EOF) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            third = getc(f);
            if (third == EOF) {
                _immediateInterrupt = savInt;
                RETURN ( nil );
            }
            fourth = getc(f);
            _immediateInterrupt = savInt;
            if (fourth == EOF) {
                RETURN ( nil );
            }
            if (_INST(position) != nil) {
                _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 4);
            }
            if (msbFlag == true) {
                value = ((first & 0xFF) << 24)
                        | ((second & 0xFF) << 16)
                        | ((third & 0xFF) << 8)
                        | (fourth & 0xFF);
            } else {
                value = ((fourth & 0xFF) << 24)
                        | ((third & 0xFF) << 16)
                        | ((second & 0xFF) << 8)
                        | (first & 0xFF);
            }
            if (value <= _MAX_INT) {
                RETURN ( _MKSMALLINT(value));
            }
            RETURN ( _makeULarge(value) );
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    binary ifFalse:[^ self errorNotBinary].
    self primitiveFailed
!

nextLong
    "in binary-mode only:
     read four bytes (msb-first) and return the value as a 32-bit unsigned 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"

%{  /* NOCONTEXT */

    FILE *f;
    char c;
    extern OBJ ErrorNumber;
    extern errno;
    OBJ pos;
    int cnt, savInt;
    extern int _immediateInterrupt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _readonly)) {
        if (_isSmallInteger(aByteValue)) {
            c = _intVal(aByteValue);
            f = MKFD(_INST(filePointer));
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
#ifdef OLD
            if (_INST(buffered) == false) {
                cnt = write(fileno(f), &c, 1);
            } else 
#endif
            {
                if (_INST(mode) == _readwrite)
                    fseek(f, 0L, 1); /* needed in stdio */
                cnt = fwrite(&c, 1, 1, f);
#ifndef OLD
                if (_INST(buffered) == false) {
                    fflush(f);
                }
#endif
            }
            _immediateInterrupt = savInt;
            if (cnt == 1) {
                pos = _INST(position);
                if (pos != nil)
                    _INST(position) = _MKSMALLINT(_intVal(pos) + 1);
                RETURN ( self );
            }
            ErrorNumber = _MKSMALLINT(errno);
            RETURN (nil);
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    self primitiveFailed
!

nextPutBytes:count from:anObject
    "write count bytes from an object starting at index start.
     return the number of bytes written or nil on error.
     Use with care - non object oriented i/o"

    ^ 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 or nil on error.
     Use with care - non object oriented i/o"

%{  /* NOCONTEXT */

    FILE *f;
    int cnt, offs;
    int objSize;
    char *cp;
    extern OBJ ErrorNumber;
    extern errno;
    OBJ pos;
    int savInt;
    extern int _immediateInterrupt;

    if (_INST(filePointer) != nil) {
        if (_INST(mode) != _readonly) {
            if (_isSmallInteger(count) && _isSmallInteger(start)) {
                cnt = _intVal(count);
                offs = _intVal(start) - 1;
                f = MKFD(_INST(filePointer));

                objSize = _Size(anObject) - OHDR_SIZE;
                if ( (offs >= 0) && (cnt >= 0) && (objSize >= (cnt + offs)) ) {
                    cp = (char *)_InstPtr(anObject) + OHDR_SIZE + offs;
                    savInt = _immediateInterrupt;
                    _immediateInterrupt = 1;
#ifdef OLD
                    if (_INST(buffered) == false) {
                        cnt = write(fileno(f), cp, cnt);
                    } else
#endif
                    {
                        if (_INST(mode) == _readwrite)
                            fseek(f, 0L, 1); /* needed in stdio */
                        cnt = fwrite(cp, 1, cnt, f);
                    }
#ifndef OLD
                    if (_INST(buffered) == false) {
                        fflush(f);
                    }
#endif
                    _immediateInterrupt = savInt;
                    if (cnt >= 0) {
                        pos = _INST(position);
                        if (pos != nil)
                            _INST(position) = _MKSMALLINT(_intVal(pos) + cnt);
                        RETURN ( _MKSMALLINT(cnt) );
                    }
                    ErrorNumber = _MKSMALLINT(errno);
                    RETURN ( nil );
                }
            }
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    self primitiveFailed
!

nextWordPut:aNumber
    "only in binary-mode:
         write the argument, aNumber as a short (two bytes);
         write msb-first for compatibility with other smalltalks."

    ^ self nextShortPut:aNumber MSB:true
!

nextShortPut:aNumber MSB:msbFlag
    "only in binary-mode:
     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."

%{  /* NOCONTEXT */

    int num;
    char bytes[2];
    FILE *f;
    extern OBJ ErrorNumber;
    extern errno;
    int savInt;
    extern int _immediateInterrupt;
    int cnt;

    if (_INST(binary) == true) {
        if (_INST(filePointer) != nil) {
            if (_INST(mode) != _readonly) {
                if (_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(_INST(filePointer));
                    savInt = _immediateInterrupt;
                    _immediateInterrupt = 1;
#ifdef OLD
                    if (_INST(buffered) == false) {
                        cnt = write(fileno(f), bytes, 2);
                    } else 
#endif
                    {
                        if (_INST(mode) == _readwrite)
                            fseek(f, 0L, 1); /* needed in stdio */
                        cnt = fwrite(bytes, 1, 2, f);
                    }
#ifndef OLD
                    if (_INST(buffered) == false) {
                        fflush(f);
                    }
#endif
                    _immediateInterrupt = savInt;
                    if (cnt == 2) {
                        if (_INST(position) != nil) {
                            _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 2);
                        }
                        RETURN ( self );
                    }
                    ErrorNumber = _MKSMALLINT(errno);
                    return ( nil );
                }
            }
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    binary ifFalse:[^ self errorNotBinary].
    self argumentMustBeInteger
!

nextLongPut:aNumber MSB:msbFlag
    "only in binary-mode:
     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."

%{  /* NOCONTEXT */

    int num;
    char bytes[4];
    FILE *f;
    extern OBJ ErrorNumber;
    extern errno;
    int cnt, savInt;
    extern int _immediateInterrupt;

    if (_INST(binary) == true) {
        if (_INST(filePointer) != nil) {
            if (_INST(mode) != _readonly) {
                if (_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(_INST(filePointer));
                    savInt = _immediateInterrupt;
                    _immediateInterrupt = 1;
#ifdef OLD
                    if (_INST(buffered) == false) {
                        cnt = write(fileno(f), bytes, 4);
                    } else 
#endif
                    {
                        cnt = fwrite(bytes, 1, 4, f);
                    }
#ifndef OLD
                    if (_INST(buffered) == false) {
                        fflush(f);
                    }
#endif
                    _immediateInterrupt = savInt;
                    if (cnt == 4) {
                        if (_INST(position) != nil) {
                            _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 4);
                        }
                        RETURN ( self );
                    }
                    ErrorNumber = _MKSMALLINT(errno);
                    return ( nil );
                }
            }
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    binary ifFalse:[^ self errorNotBinary].

    aNumber isInteger ifTrue:[
        (self nextShortPut:(aNumber // 16r10000) MSB:msbFlag) isNil ifTrue:[^ nil].
        ^ self nextShortPut:(aNumber \\ 16r10000) MSB:msbFlag.
    ].
    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;
    int savInt;
    extern int _immediateInterrupt;

    if (_INST(filePointer) != nil) {
        if (_INST(mode) != _writeonly) {
#ifdef OLD
            if (_INST(buffered) == true) 
#endif
            {
                f = MKFD(_INST(filePointer));
                savInt = _immediateInterrupt;
                _immediateInterrupt = 1;
                c = getc(f);
                _immediateInterrupt = savInt;
                if (c != EOF) {
                    ungetc(c, f);
                    if (_INST(binary) == true) {
                        RETURN ( _MKSMALLINT(c & 0xFF) );
                    }
                    RETURN ( _MKCHARACTER(c & 0xFF) );
                }
                RETURN ( nil );
            }
        }
    }
%}
.
    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;
    int savInt;
    unsigned char ch;

    extern int _immediateInterrupt;

    if (_INST(filePointer) != nil) {
        if (_INST(mode) != _writeonly) {
            f = MKFD(_INST(filePointer));
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            do {
#ifdef OLD
                if (_INST(buffered) == false) {
                    if (read(fileno(f), &ch, 1) != 1)
                        c = EOF;
                    else
                        c = ch;
                } else 
#endif
                {
                    if (_INST(mode) == _readwrite)
                        fseek(f, 0L, 1); /* needed in stdio */
                    c = getc(f);
                }
            } while ((c < 0) && (errno == EINTR));

            _immediateInterrupt = savInt;
            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;
            RETURN ( nil );
        }
    }
%}
.
    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 new:count
    ] ifFalse:[
        coll := String new:count
    ].
    1 to:count do: [:index |
        coll at:index put:(self next)
    ].
    ^ coll
! !

!ExternalStream methodsFor:'writing'!

synchronizeOutput
    "write all buffered data - for buffered mode only"

%{  /* NOCONTEXT */

    if (_INST(filePointer) != nil) {
        if (_INST(mode) != _readonly) {
            if (_INST(buffered) == true) {
                fflush( MKFD(_INST(filePointer)) );
            }
        }
    }
%}
!

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

%{  /* NOCONTEXT */

    FILE *f;
    char c;
    extern OBJ ErrorNumber;
    extern errno;
    int cnt;
    OBJ pos;
    int savInt;
    extern int _immediateInterrupt;

    if (_INST(filePointer) != nil) {
        if (_INST(mode) != _readonly) {
            if (_INST(binary) != true) {
                if (_isCharacter(aCharacter)) {
                    c = _intVal(_CharacterInstPtr(aCharacter)->c_asciivalue);
    doWrite:
                    f = MKFD(_INST(filePointer));

                    savInt = _immediateInterrupt;
                    _immediateInterrupt = 1;
#ifdef OLD
                    if (_INST(buffered) == false) {
                        cnt = write(fileno(f), &c, 1);
                    } else 
#endif
                    { 
                        if (_INST(mode) == _readwrite)
                            fseek(f, 0L, 1); /* needed in stdio */
                        cnt = fwrite(&c, 1, 1, f);
                    }
#ifndef OLD
                    if (_INST(buffered) == false) {
                        fflush(f);
                    }
#endif
                    _immediateInterrupt = savInt;
                    if (cnt == 1) {
                        pos = _INST(position);
                        if (pos != nil) {
                            _INST(position) = _MKSMALLINT(_intVal(pos) + 1);
                        }
                        RETURN ( self );
                    }
                    ErrorNumber = _MKSMALLINT(errno);
                    RETURN ( nil );
                }
            } else {
                if (_isSmallInteger(aCharacter)) {
                    c = _intVal(aCharacter);
                    goto doWrite;
                }
            }
        }
    }
%}
.
    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"

%{  /* NOCONTEXT */

    FILE *f;
    unsigned char *cp;
    int len, cnt;
    extern OBJ ErrorNumber;
    extern errno;
    OBJ pos;
    int savInt;
    extern int _immediateInterrupt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _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);
                }
            }
        }
        if (cp != NULL) {
            f = MKFD(_INST(filePointer));

            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
#ifdef OLD
            if (_INST(buffered) == false) {
                cnt = write(fileno(f), cp, len);
            } else 
#endif
            { 
                if (_INST(mode) == _readwrite)
                    fseek(f, 0L, 1); /* needed in stdio */
                cnt = fwrite(cp, 1, len, f);
            }
#ifndef OLD
                    if (_INST(buffered) == false) {
                        fflush(f);
                    }
#endif
            _immediateInterrupt = savInt;
            if (cnt == len) {
                pos = _INST(position);
                if (pos != nil) {
                    _INST(position) = _MKSMALLINT(_intVal(pos) + len);
                }
                RETURN ( self );
            }
            ErrorNumber = _MKSMALLINT(errno);
            RETURN ( nil );
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].

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

nextPut:aCollection from:start to:stop
    "write a range of elements of the argument, aCollection"

%{  /* NOCONTEXT */

    FILE *f;
    unsigned char *cp;
    int len, cnt, index1, index2;
    extern OBJ ErrorNumber;
    extern errno;
    int savInt;
    extern int _immediateInterrupt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _readonly)) {
        if (_isSmallInteger(start) && _isSmallInteger(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);
                }
            }
            if (cp != NULL) {
                f = MKFD(_INST(filePointer));
                index1 = _intVal(start);
                index2 = _intVal(stop);
                if ((index1 < 1) || (index2 > len) || (index2 < index1)) {
                    RETURN ( self );
                }
                if (index2 > len)
                    index2 = len;

                savInt = _immediateInterrupt;
                _immediateInterrupt = 1;
                len = index2 - index1 + 1;
#ifdef OLD
                if (_INST(buffered) == false) {
                    cnt = write(fileno(f), cp + index1 - 1, len);
                } else 
#endif
                { 
                    if (_INST(mode) == _readwrite)
                        fseek(f, 0L, 1); /* needed in stdio */
                    cnt = fwrite(cp + index1 - 1, 1, len, f);
                }
#ifndef OLD
                    if (_INST(buffered) == false) {
                        fflush(f);
                    }
#endif
                _immediateInterrupt = savInt;
                if (cnt == len) {
                    if (_INST(position) != nil) {
                        _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + len);
                    }
                    RETURN ( self );
                }
                ErrorNumber = _MKSMALLINT(errno);
                RETURN ( nil );
            }
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].

    start to:stop do:[:index |
        self nextPut:(aCollection at:index)
    ]
!

cr
    "reimplemented for speed"

%{  /* NOCONTEXT */

    FILE *f;
    extern OBJ ErrorNumber;
    extern errno;
    extern int _immediateInterrupt;
    int cnt, savInt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _readonly)) {
        if (_INST(binary) != true) {
            f = MKFD(_INST(filePointer));

            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
#ifdef OLD
            if (_INST(buffered) == false) {
                cnt = write(fileno(f), "\n", 1);
            } else 
#endif
            { 
                if (_INST(mode) == _readwrite)
                    fseek(f, 0L, 1); /* needed in stdio */
                cnt = fwrite("\n", 1, 1, f);
            }
#ifndef OLD
                    if (_INST(buffered) == false) {
                        fflush(f);
                    }
#endif
            _immediateInterrupt = savInt;
            if (cnt == 1) {
                if (_INST(position) != nil) {
                    _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + 1);
                }
                RETURN ( self );
            }
            ErrorNumber = _MKSMALLINT(errno);
            return ( nil );
        }
    }
%}
.
    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."

%{  /* STACK:2000 */

    FILE *f;
    int len;
    char buffer[1024];
    extern int _immediateInterrupt;
    int savInt;
    char *rslt;
    extern errno;
    int fd;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
        if (_INST(binary) != true) {
            f = MKFD(_INST(filePointer));
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            buffer[0] = 0;

#ifndef OLD
            if (_INST(mode) == _readwrite)
                fseek(f, 0L, 1); /* needed in stdio */
#endif
#ifdef OLD
            if (_INST(buffered) == true) {
#endif
                do {
                    rslt = fgets(buffer, sizeof(buffer), f);
                } while ((rslt == NULL) && (errno == EINTR));
#ifdef OLD
            } else {
                rslt = buffer;
                fd = fileno(f);
                for (;;) {
                    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 == (buffer + sizeof(buffer) - 1)) {
                        *rslt = '\0';
                        break;
                    }
                }
            }
#endif
            _immediateInterrupt = savInt;
            if (rslt != NULL) {
                len = strlen(buffer);
                if (_INST(position) != nil) {
                    _INST(position) = _MKSMALLINT(_intVal(_INST(position)) + len);
                }
                /* 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) );
            }
            RETURN ( nil );
        }
    }
%}
.
    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;
    char *s;
    extern OBJ ErrorNumber;
    extern errno;
    int savInt;
    extern int _immediateInterrupt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _readonly)) {
        if (_INST(binary) != true) {
            if (_isString(aString)) {
                f = MKFD(_INST(filePointer));
                s = (char *) _stringVal(aString);
                len = _stringSize(aString);

                savInt = _immediateInterrupt;
                _immediateInterrupt = 1;
#ifdef OLD
                if (_INST(buffered) == false) {
                    cnt = write(fileno(f), s, len);
                } else 
#endif
                { 
                    if (_INST(mode) == _readwrite)
                        fseek(f, 0L, 1); /* needed in stdio */
                    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) {
                        fflush(f);
                    }
#endif
                    if (cnt == 1) {
                        pos = _INST(position);
                        if (pos != nil) {
                            _INST(position) = _MKSMALLINT(_intVal(pos)+len+1);
                        }
                        _immediateInterrupt = savInt;
                        RETURN ( self );
                    }
                }
                _immediateInterrupt = savInt;
                ErrorNumber = _MKSMALLINT(errno);
                RETURN ( nil );
            }
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #readonly) ifTrue:[^ self errorReadOnly].
    binary ifTrue:[^ self errorBinary].
    self argumentMustBeString
!

nextPutLinesFrom:aStream upToLineStartingWith:aStringOrNil
    "used to copy large files
     - read from aStream up to and including a line starting with aStringOrNil
     and append it to self. If aStringOrNil is nil or not matched,
     copy preceeds to the end"

    |srcFilePointer|

    (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];
    extern int _immediateInterrupt;
    int savInt;

    if (_isSmallInteger(srcFilePointer) 
#ifdef OLD
     && (_INST(buffered) == true)
#endif
    ) {
        if ((aStringOrNil == nil) || _isString(aStringOrNil)) {
            if (aStringOrNil != nil) {
                matchString = (char *) _stringVal(aStringOrNil);
                matchLen = _stringSize(aStringOrNil);
            }
            dst = MKFD(_INST(filePointer));
            src = (FILE *)_intVal(srcFilePointer);
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            for (;;) {
                if (fgets(buffer, sizeof(buffer), src) == NULL) break;
                if (fputs(buffer, dst) == EOF) break;
#ifndef OLD
                    if (_INST(buffered) == false) {
                        fflush(dst);
                    }
#endif
                if (matchLen) {
                    if (strncmp(matchString, buffer, matchLen) == 0) 
                        break;
                }
            }
            _immediateInterrupt = savInt;
            _INST(position) = nil;
            RETURN ( self );
        }
    }
%}
.
    buffered ifFalse:[^ self errorNotBuffered].
    ^ self primitiveFailed
!

peekForLineStartingWith:aString
    "read ahead for next line starting with aString;
     return the line-string if found, nil otherwise..
     do not advance position i.e. nextLine will reread this line"

    (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, lastpos;
    extern int _immediateInterrupt;
    int savInt;

    if (_isString(aString)) {
        matchString = (char *) _stringVal(aString);
        l = _stringSize(aString);

        f = MKFD(_INST(filePointer));
        firstpos = ftell(f);
        for (;;) {
            if (_INST(mode) == _readwrite)
                fseek(f, 0L, 1); /* needed in stdio */
            lastpos = ftell(f);
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            do {
                cp = fgets(buffer, sizeof(buffer), f);
            } while ((cp == NULL) && (errno == EINTR));
            _immediateInterrupt = savInt;
            if (cp == NULL) {
                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) );
    }
%}
.
    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.
        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;

    if (_INST(filePointer) != nil) {
        f = MKFD(_INST(filePointer));
        RETURN ( feof(f) ? true : false );
    }
%}
.
    self errorNotOpen
! !

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

    |fd sema|

    fd := self fileDescriptor.
    sema := Semaphore new.

    [OperatingSystem readCheck:fd] whileFalse:[
        Processor enableSemaphore:sema onInput:fd.
        Processor currentProcess state:#ioWait.
        sema wait.
        Processor disableSemaphore:sema
    ]
!

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

    |fd sema|

    fd := self fileDescriptor.
    sema := Semaphore new.

    [OperatingSystem writeCheck:fd] whileFalse:[
        Processor enableSemaphore:sema onOutput:fd.
        Processor currentProcess state:#ioWait.
        sema wait.
        Processor disableSemaphore:sema
    ]
! !
     
!ExternalStream methodsFor:'reimplemented for speed'!

peekFor:anObject
    "return true and move past if next == something."

%{  /* NOCONTEXT */

    FILE *f;
    int c;
    int peekValue;
    extern int _immediateInterrupt;
    int savInt;

    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) {
        if (_INST(filePointer) != nil) {
            f = MKFD(_INST(filePointer));
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            c = getc(f);
            _immediateInterrupt = savInt;
            if (c == peekValue) {
                _INST(position) = nil;
                RETURN ( true );
            }
            ungetc(c, f);
            RETURN ( false );
        }
    }
%}
.
    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;
    extern int _immediateInterrupt;
    int savInt;

    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) {
        if (_INST(filePointer) != nil) {
            if (_INST(mode) != _writeonly) {
                f = MKFD(_INST(filePointer));
                savInt = _immediateInterrupt;
                _immediateInterrupt = 1;
                _INST(position) = nil;
                if (_INST(mode) == _readwrite)
                    fseek(f, 0L, 1); /* needed in stdio */
                for (;;) {
                    c = getc(f);
                    if (c == EOF) {
                        _immediateInterrupt = savInt;
                        RETURN (nil);
                    }
                    if (c == peekValue) {
                        _immediateInterrupt = savInt;
                        RETURN (anObject);
                    }
                }
                _immediateInterrupt = savInt;
            }
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ super nextMatchFor:anObject
!

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

%{  /* STACK:2000 */

    FILE *f;
    char buffer[1024];
    extern int _immediateInterrupt;
    int savInt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
        if (_INST(binary) != true) {
            f = MKFD(_INST(filePointer));
            savInt = _immediateInterrupt;
            _immediateInterrupt = 1;
            if (_INST(mode) == _readwrite)
                fseek(f, 0L, 1); /* needed in stdio */
            if (fgets(buffer, sizeof(buffer), f) != NULL) {
                _immediateInterrupt = savInt;
                RETURN ( self );
            }
            _immediateInterrupt = savInt;
            RETURN ( nil );
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    binary ifTrue:[^ self errorBinary].
    self errorWriteOnly
!

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 buffer l first idx|

    (aString isKindOf:String) ifTrue:[
        oldPos := self position.
        l := aString size.
        first := aString at:1.
        buffer := String new:l.
        [true] whileTrue:[
            (self nextBytes:l into:buffer) == l ifFalse:[
                self position:oldPos.
                ^ nil
            ].
            buffer = aString ifTrue:[
                self position:(self position - l).
                ^ self
            ].
            idx := buffer indexOf:first startingAt:2.
            idx == 0 ifFalse:[
                self position:(self position - l + idx - 1)
            ]
        ]
    ].
    ^ super skipFor:aString
!

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;
    extern int _immediateInterrupt;
    int savInt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
        if (_INST(binary) != true) {
            f = MKFD(_INST(filePointer));
            if (_INST(mode) == _readwrite)
                fseek(f, 0L, 1); /* needed in stdio */
            while (1) {
                if (feof(f)) {
                    RETURN ( nil );
                }
                savInt = _immediateInterrupt;
                _immediateInterrupt = 1;
                c = getc(f);
                _immediateInterrupt = savInt;
                if (c < 0) {
                    RETURN ( nil );
                }
                switch (c) {
                    case ' ':
                    case '\t':
                    case '\n':
                    case '\r':
                    case '\b':
                    case '\014':
                        break;
                    default:
                        ungetc(c, f);
                        RETURN ( _MKCHARACTER(c & 0xFF) );
                }
            }
        }
    }
%}
.
    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;
    extern int _immediateInterrupt;
    int savInt;

    if ((_INST(filePointer) != nil) && (_INST(mode) != _writeonly)) {
        if (_INST(binary) != true) {
            f = MKFD(_INST(filePointer));
            while (1) {
                if (_INST(mode) == _readwrite)
                    fseek(f, 0L, 1); /* needed in stdio */
                if (feof(f)) {
                    RETURN ( nil );
                }
                savInt = _immediateInterrupt;
                _immediateInterrupt = 1;
                c = getc(f);
                _immediateInterrupt = savInt;
                if (c < 0) {
                    RETURN ( nil );
                }
                switch (c) {
                    case ' ':
                    case '\t':
                    case '\b':
                        break;
                    default:
                        ungetc(c, f);
                        RETURN ( _MKCHARACTER(c & 0xFF) );
                }
            }
        }
    }
%}
.
    filePointer isNil ifTrue:[^ self errorNotOpen].
    (mode == #writeonly) ifTrue:[^ self errorWriteOnly].
    self errorBinary
!

nextChunk
    "return the next chunk, i.e. all characters up to the next
     non-doubled exclamation mark; undouble doubled exclamation marks.
     - reimplemented for speed"
    |retVal|

    filePointer isNil ifTrue:[
        ^ self errorNotOpen
    ].
    binary ifTrue:[
        ^ self errorBinary
    ].
%{
    FILE *f;
    int done = 0;
    REGISTER int c;
    unsigned char peekC;
    char *buffer, *newBuffer;
    REGISTER int index;
    int currSize;
    int inComment, inString, inPrimitive = 0;
    extern int _immediateInterrupt;
    int savInt;

    f = MKFD(_INST(filePointer));
    if (_INST(mode) == _readwrite)
        fseek(f, 0L, 1); /* needed in stdio */
    /*
     * skip spaces
     */
    savInt = _immediateInterrupt;
    _immediateInterrupt = 1;
    while (! done) {
        if (feof(f)) {
            _immediateInterrupt = savInt;
            RETURN ( nil );
        }
        do {
            c = getc(f);
        } while ((c < 0) && (errno == EINTR));
        switch (c) {
            case ' ':
            case '\t':
            case '\n':
            case '\r':
            case '\b':
            case '\014':
                break;

            case EOF:
                _immediateInterrupt = savInt;
                RETURN ( nil );

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

    /*
     * read chunk into a buffer
     */
    buffer = (char *)malloc(3000);
    currSize = 3000;
    index = 0;
    while (! feof(f)) {
        /* do we have to resize the buffer ? */
        if ((index+2) >= currSize) {
            newBuffer = (char *)malloc(currSize * 2);
            bcopy(buffer, newBuffer, index);
            free(buffer);
            buffer = newBuffer;
            currSize = currSize * 2;
        }
        do {
            c = getc(f);
        } while (c < 0 && (errno == EINTR));
        if (c == '%') {
            peekC = getc(f);
            ungetc(peekC, f);
            if (peekC == '{') {
                inPrimitive++;
            } else if (peekC == '}') {
                inPrimitive--;
            }
        } else {
            if (! inPrimitive) {
                if (c == '!') {
                    c = getc(f);
                    if (c != '!') {
                        ungetc(c, f);
                        break;
                    }
                }
            }
        }
        if (c == EOF) break;
        buffer[index++] = c;
    }
    _immediateInterrupt = savInt;
    buffer[index] = '\0';
    /*
     * make it a string
     */
    retVal = _MKSTRING(buffer COMMA_CON);
    free(buffer);
%}
.
    ^ retVal
! !