FileStream.st
author Claus Gittinger <cg@exept.de>
Sat, 04 Oct 1997 19:01:30 +0200
changeset 2998 930360fb3f12
parent 2992 197c2c222030
child 3006 b3530950854a
permissions -rw-r--r--
#size is not really obsolete

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

ExternalStream subclass:#FileStream
	instanceVariableNames:'pathName canPosition'
	classVariableNames:''
	poolDictionaries:''
	category:'Streams-External'
!

!FileStream primitiveDefinitions!
%{
#ifdef __openVMS__
# undef __new
#endif

#include <stdio.h>
#define _STDIO_H_INCLUDED_

#include <errno.h>
#define _ERRNO_H_INCLUDED_

#ifdef transputer
# include <iocntrl.h>
# ifndef fileno
   /* kludge: inmos forgot fileno */
#  define fileno(f)     ((f)->__file)
# endif
#else
# include <sys/types.h>
# include <sys/stat.h>
#endif

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

#ifndef SEEK_SET
# define SEEK_SET       0
#endif
#ifndef SEEK_CUR
# define SEEK_CUR       1
#endif
#ifndef SEEK_END
# define SEEK_END       2
#endif

/*
 * not all systems have off_t
 * explicit add of those we know to have ...
 */
#ifdef __osf__
# define OFF_T  off_t
#endif

#ifndef OFF_T
# define OFF_T  long
#endif

#ifdef __VMS__
/*
 * get those VMS definitions ...
 */
# include <rms.h>
#endif

#ifndef WIN32
 extern long ftell(), lseek();
#endif

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

%}
! !

!FileStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    This class provides access to the operating systems underlying file
    system (i.e. its an interface to the stdio library).

    Notice, that on some systems, the standard I/O library has performance
    problems when a file is opened for readwrite. 
    For best results, open files either readonly or writeonly.

    Also notice, that some OperatingSystems do not fully support
    positioning a file stream.
    For example, poor VMS does not allow positioning onto arbitrary
    byte boundaries if the file is a variable-record-RMS file.
    (stupid enough, this is the default for textfiles as created by
     some tools ...)
    Therefore, the instance variable canPosition is set according to
    this and an error is raised, if a position: is attemted.
    I know, this is ugly, but what else could we do ?

    [instance variables:]
	pathName	<String>	the files path (if known)
	canPosition	<Boolean>	positionable - read above comment

    [author:]
	Claus Gittinger

    [see also:]
	Filename DirectoryStream PipeStream Socket
"
!

examples
"
  for VMS users only:

    The #openWithMode:attributes: entry allows additional RMS attributes
    to be passed in the second argument, which must be an array of strings
    as described in the 'creat' RTL Library documentation.

    For example, to create a file with fixed records and recordLength of 100,
    use:

	|newFile|

	newFile := FileStream new pathName:'<nameOfFile>'.
	newFile setMode:#writeonly.
	newFile openWithMode:'w' attributes:#('rfm=fix' 'fsz=100').

    since all of the above is private protocol, and it is considered bad style to
    access these from user programs, we recommend subclassing FileStream as
    something like VMSFixedRecordFileStream, and redefine the instance creation
    method(s) there as appropriate. 
    This will retain VMS specifics in one place and enhance maintanability.
"
! !

!FileStream class methodsFor:'initialization'!

initialize
    OpenErrorSignal isNil ifTrue:[
	"/
 	"/ this is temporary - for now allow an openError to
	"/ be unhandled and proceed by returning a nil from the
	"/ stream creation method.
	"/ In the future, this will be a hard signal.
	"/
        OpenErrorSignal := QuerySignal new mayProceed:true.
	OpenErrorSignal parent:(super openErrorSignal).
        OpenErrorSignal nameClass:self message:#openErrorSignal.
        OpenErrorSignal notifierString:'open error'.
    ]
! !

!FileStream class methodsFor:'instance creation'!

appendingOldFileNamed:filename
    "return a FileStream for existing file named filename, aString.
     The file is opened for writeonly access."

    |newStream|
    newStream := self new pathName:filename.
    newStream openForAppending isNil ifTrue:[^nil].
"
    this is not a good idea; I might like to read the written stuff ...

    newStream readLimit:(newStream size).
"
    ^ newStream
!

appendingOldFileNamed:filename in:aDirectory
    "return a FileStream for existing file named filename, aString
     in aDirectory, a FileDirectory.
     The file is opened for writeonly access."

    |newStream|
    newStream := self new pathName:filename in:aDirectory.
    newStream openForAppending isNil ifTrue:[^nil].
"
    this is not a good idea; I might like to read the written stuff ...

    newStream readLimit:(newStream size).
"
    ^ newStream
!

fileNamed:filename
    "return a stream on file filename - if the file does not
     already exist, create it.
     The file is opened for read/write access."

    |stream|

    stream := self oldFileNamed:filename.
    stream isNil ifTrue:[
	stream := self newFileNamed:filename
    ].
    ^ stream
!

fileNamed:filename in:aDirectory
    "return a stream on file filename - if the file does not
     already exist, create it.
     The file is opened for read/write access."

    |stream|

    stream := self oldFileNamed:filename in:aDirectory.
    stream isNil ifTrue:[
	stream := self newFileNamed:filename in:aDirectory
    ].
    ^ stream
!

newFileForWritingNamed:filename
    "return a FileStream for new file named filename, aString.
     If the file exists, it is truncated, otherwise created.
     The file is opened for writeonly access."

    |newStream|
    newStream := self new pathName:filename.
    newStream createForWriting isNil ifTrue:[^nil].
    ^ newStream
!

newFileForWritingNamed:filename in:aDirectory
    "return a FileStream for new file named filename, aString
     in aDirectory, a FileDirectory.
     If the file exists, it is truncated, otherwise created.
     The file is opened for writeonly access."

    |newStream|
    newStream := self new pathName:filename in:aDirectory.
    newStream createForWriting isNil ifTrue:[^nil].
    ^ newStream
!

newFileNamed:filename
    "return a FileStream for new file named filename, aString.
     If the file exists, it is truncated, otherwise created.
     The file is opened for read/write access."

    |newStream|
    newStream := self new pathName:filename.
    newStream createForReadWrite isNil ifTrue:[^nil].
    ^ newStream
!

newFileNamed:filename in:aDirectory
    "return a FileStream for new file named filename, aString
     in aDirectory, a FileDirectory.
     If the file exists, it is truncated, otherwise created.
     The file is opened for read/write access."

    |newStream|
    newStream := self new pathName:filename in:aDirectory.
    newStream createForReadWrite isNil ifTrue:[^nil].
    ^ newStream
!

oldFileNamed:filename
    "return a FileStream for existing file named filename, aString.
     The file is opened for read/write access."

    |newStream|

    (OperatingSystem isReadable:filename) ifFalse:[^nil].
    newStream := self new pathName:filename.
    newStream readwrite.
    newStream openForReadWrite isNil ifTrue:[^nil].
"
    this is not a good idea; someone else might be appending ...

    newStream readLimit:(newStream size).
"
    ^ newStream
!

oldFileNamed:filename in:aDirectory
    "return a FileStream for existing file named filename, aString
     in aDirectory, a FileDirectory.
     The file is opened for read/write access."

    |newStream|
    newStream := self new pathName:filename in:aDirectory.
    newStream openForReadWrite isNil ifTrue:[^nil].
"
    this is not a good idea; someone else might be appending ...

    newStream readLimit:(newStream size).
"
    ^ newStream
!

readonlyFileNamed:filename
    "return a readonly FileStream for existing file named filename, aString"

    |newStream|

    (OperatingSystem isReadable:filename) ifFalse:[^nil].

    newStream := self new pathName:filename.
    newStream openForReading isNil ifTrue:[^nil].
"
    this is not a good idea; someone else might be appending ...

    newStream readLimit:(newStream size).
"
    ^ newStream
!

readonlyFileNamed:filename in:aDirectory
    "return a readonly FileStream for existing file named filename, aString
     in aDirectory, a FileDirectory"

    |newStream|
    newStream := self new pathName:filename in:aDirectory.
    newStream openForReading isNil ifTrue:[^nil].
"
    this is not a good idea; someone else might be appending ...

    newStream readLimit:(newStream size).
"
    ^ newStream
! !

!FileStream methodsFor:'accessing'!

directoryName
    "return the name of the directory I'm in as a string"

    ^ pathName asFilename directoryName
!

name
    "return my name without leading direcory-path (i.e. the plain fileName)
     as a string"

    ^ pathName asFilename baseName
!

pathName
    "return the pathname"

    ^ pathName
!

store:something
    "what really should this do"

    self nextPutAll:something storeString
! !

!FileStream methodsFor:'error handling'!

openError
    "{ Pragma: +optSpace }"

    "report an error, that file open failed"

    "/
    "/ for now, error on open only raises a querySignal.
    "/ If its not handled, a failing open will return nil.
    "/ Currently, all users of fileStream check for this
    "/ nil return value (which is a historic leftover)
    "/
    "/ This will change in one of the next ST/X releases - for
    "/ now, it is best to provide an exceptionHandler AND check the
    "/ return value. 
    "/ Sorry about that.
    "/
    LastErrorNumber := lastErrorNumber.
    super openError.
    ^ nil
! !

!FileStream methodsFor:'positioning'!

position
    "return the read/write position in the file -
     notice, in smalltalk indices start at 1 so begin of file is 1"

%{  /* NOCONTEXT */

    FILE *f;
    long currentPosition;

    if (__INST(filePointer) != nil) {
	f = __FILEVal(__INST(filePointer));
	do {
	    if (__INST(buffered) == true) {
		currentPosition = ftell(f);
	    } else {
		currentPosition = lseek(fileno(f), 0L, SEEK_CUR);
	    }
	} while ((currentPosition < 0) && (errno == EINTR));
	if (currentPosition >= 0) {
	    /*
	     * notice: Smalltalk index starts at 1
	     */
	    RETURN ( __MKSMALLINT(currentPosition + 1) );
	}
	__INST(lastErrorNumber) = __MKSMALLINT(errno);
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self ioError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ self primitiveFailed
!

position:newPos
    "set the read/write position in the file"

%{  /* NOCONTEXT */

    FILE *f;
    long ret;
    OBJ fp;
    long nP;

    if ((__INST(canPosition) != false) 
     || (newPos == __MKSMALLINT(1))) {
        if ((fp = __INST(filePointer)) != nil) {
	    if (__isSmallInteger(newPos)) {
	        f = __FILEVal(fp);
	        nP = (long)__intVal(newPos);

	        /*
	         * notice: Smalltalk index starts at 1
	         */
	        nP--;

	        do {
		    if (__INST(buffered) == true) {
		        ret = fseek(f, nP, SEEK_SET);
		    } else {
		        ret = lseek(fileno(f), nP, SEEK_SET);
		    }
	        } while ((ret < 0) && (errno == EINTR));
	        if (ret >= 0) {
		    __INST(position) = newPos;
		    /*
		     * just to make certain ...
		     */
		    __INST(hitEOF) = false;
		    RETURN ( self );
	        }
	        __INST(lastErrorNumber) = __MKSMALLINT(errno);
	    }
	}
    }
%}.
    canPosition == false ifTrue:[
	"/ position by rewinding & re-reading everything up-to
	"/ that point.
	^ self slowPosition:newPos
    ].
    lastErrorNumber notNil ifTrue:[
	(OperatingSystem errorSymbolForNumber:lastErrorNumber) == #EINVAL ifTrue:[
	    "/ invalid position
	    ^ self positionError
	].
	"/ assume I/O error
	^ self ioError
    ].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ self primitiveFailed
!

setToEnd
    "set the read/write position in the file to be at the end of the file"

%{
    FILE *f;
    long ret;

    if (__INST(filePointer) != nil) {
	f = __FILEVal(__INST(filePointer));
	__INST(position) = nil;
	do {
	    if (__INST(buffered) == true) {
		ret = fseek(f, 0L, SEEK_END);
	    } else {
		ret = lseek(fileno(f), 0L, SEEK_END);
	    }
	} while ((ret < 0) && (errno == EINTR));
	if (ret >= 0) {
	    RETURN ( self );
	}
	__INST(lastErrorNumber) = __MKSMALLINT(errno);
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self ioError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ self primitiveFailed
!

slowPosition:newPos
    "position the file by re-reading everything up-to newPos.
     The effect is the same as that of #position:, but its much slower.
     This is required to reposition nonPositionable streams, such
     as tape-streams or variable-record-RMS files under VMS.
     Caveat:
         This should really be done transparently by the stdio library."

    |buffer amount|

    self isReadable ifFalse:[
	"/ sorry
	^ self positionError
    ].

    buffer := ByteArray new:8*1024.

    (position isNil "/ i.e. unknown
    or:[newPos < position]) ifTrue:[
        self reset.
    ].
    [position < newPos] whileTrue:[
	amount := (buffer size) min:(newPos-position).
	(self nextBytes:amount into:buffer startingAt:1) ~~ amount ifTrue:[
	    ^ self positionError
	].
    ].
    "/ ('FileStream [info]: slow position - please convert ''' , pathName printString , ''' to streamLF format') infoPrintCR.
! !

!FileStream methodsFor:'printing & storing'!

printOn:aStream
    "append a human readable representation of the receiver to aStream"

    aStream nextPutAll:'(a FileStream for:'.
    aStream nextPutAll:pathName printString.
    aStream nextPut:$)

    "Modified: 30.7.1997 / 13:51:01 / cg"
!

storeOn:aStream
    "append a representation of the receiver to aStream,
     from which a copy can be reconstructed later."

    aStream nextPutAll:'(FileStream oldFileNamed:'.
    aStream nextPutAll:pathName storeString.
    (self position ~~ 1) ifTrue:[
        aStream nextPutAll:'; position:'.
        self position storeOn:aStream
    ].
    aStream nextPut:$)

    "Modified: 30.7.1997 / 16:43:50 / cg"
! !

!FileStream methodsFor:'private'!

createForReadWrite
    "create/truncate the file for read/write.
     If the file existed, its truncated; otherwise its created."

    mode := #readwrite.
    ^ self openWithMode:CreateReadWriteMode
!

createForWriting
    "create/truncate the file for writeonly.
     If the file existed, its truncated; otherwise its created."

    mode := #writeonly.
    didWrite := true.
    ^ self openWithMode:WriteMode
!

open
    "open the file"

    pathName isNil ifTrue:[^nil].
    (mode == #readonly) ifTrue: [
	didWrite := false.
	^ self openWithMode:ReadMode
    ].
    (mode == #writeonly) ifTrue: [
	didWrite := true.
	^ self openWithMode:WriteMode
    ].
    ^ self openWithMode:ReadWriteMode
!

openForAppending
    "open the file for writeonly appending to the end.
     If the file does not exist its an error, return nil; 
     otherwise return the receiver."

    mode := #writeonly.
    didWrite := true.
    ^ self openWithMode:AppendMode
!

openForReadWrite
    "open the file for read/write.
     If the file does not exist its an error, return nil; 
     otherwise return the receiver."

    mode := #readwrite.
    ^ self openWithMode:ReadWriteMode
!

openForReading
    "open the file for readonly.
     If the file does not exist its an error, return nil; 
     otherwise return the receiver."

    mode := #readonly.
    didWrite := false.
    ^ self openWithMode:ReadMode
!

openForWriting
    "open the file writeonly.
     If the file does not exist its an error, return nil; 
     otherwise return the receiver."

    mode := #writeonly.
    didWrite := true.
    ^ self openWithMode:ReadWriteMode   "unix-io does not allow this; open for update here"
!

openWithMode:openmode
    "open the file;
     openmode is the string defining the way to open as defined by the stdio library
     (i.e. the 2nd fopen argument).

     This is a private entry, but maybe useful to open a file in a special mode,
     which is proprietrary to the operatingSystem."
     
    ^ self openWithMode:openmode attributes:nil
!

openWithMode:openmode attributes:attributeSpec
    "open the file; 
     openmode is the string defining the way to open as defined by the stdio library
     (i.e. the 2nd fopen argument).

     attributeSpec is an additional argument, only used with VMS - it allows a file to
     be created as fixedRecord, variableRecord, streamLF, streamCR, ...
     In VMS, if nonNil, it must consist of an array of strings (max:10), giving additional
     attributes (see fopen description).
     Passing a nil specifies the default format (streamLF) - ST/X always invokes this with nil.
     This argument is ignored in UNIX & MSDOS systems.

     This is a private entry, but maybe useful to open/create a file in a special mode,
     which is proprietrary to the operatingSystem."

    |ok|

    filePointer notNil ifTrue:[^ self errorOpen].
    ok := false.
%{
    FILE *f;
    FILE *fopen();
    OBJ path, fp;
    int pass = 0;

retry:
    path = __INST(pathName);
    if (__isNonNilObject(path) && (__qClass(path)==String)) {
	__BEGIN_INTERRUPTABLE__
	do {
#ifdef __VMS__
	    /*
	     * allow passing additional RMS arguments.
	     * stupid: they do not seem to offer an interface for passing a char **.
	     */
	    errno = 0;

	    {
		if (__isArray(attributeSpec)) {
		    OBJ *ap = __ArrayInstPtr(attributeSpec)->a_element;
		    int numAttrib = 0;
		    int i;

		    numAttrib = __arraySize(attributeSpec);
		    for (i=0; i<numAttrib;i++) {
			if (! __isString(ap[i])) {
		            f = NULL;
		            errno = EINVAL; /* invalid argument */
			    goto getOutOfHere;
			}
		    }
		    switch (numAttrib) {
			case 0:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode));
			    break;
			case 1:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]));
			    break;
			case 2:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]));
			    break;
			case 3:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]));
			    break;
			case 4:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]));
			    break;
			case 5:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]));
			    break;
			case 6:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]), __stringVal(ap[5]));
			    break;
			case 7:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]), __stringVal(ap[5]),
				      __stringVal(ap[6]));
			    break;
			case 8:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]), __stringVal(ap[5]),
				      __stringVal(ap[6]), __stringVal(ap[7]));
			    break;
			case 9:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]), __stringVal(ap[5]),
				      __stringVal(ap[6]), __stringVal(ap[7]), __stringVal(ap[8]));
			    break;
			case 10:
			    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]), __stringVal(ap[5]),
				      __stringVal(ap[6]), __stringVal(ap[7]), __stringVal(ap[8]),
				      __stringVal(ap[9]));
			    break;
		  	default:
			    f = NULL;
			    errno = E2BIG; /* too many args */
			    goto getOutOfHere;
		    }
		} else if (attributeSpec != nil) {
		    f = NULL;
		    errno = EINVAL; /* invalid argument */
		    goto getOutOfHere;
		} else {
	            /*
	             * create file as sequential streamLF by default.
	             */
	    	    f = fopen((char *)__stringVal(path), (char *)__stringVal(openmode), "rfm=stmlf");
		}
	    }
#else
# ifdef LINUX
	    /* 
	     * LINUX may return a non-NULL f even when interrupted.
	     * Therefore, check errno and fake a null-return.
	     */
	    errno = 0;
	    f = fopen((char *) __stringVal(path), (char *) __stringVal(openmode));
	    if (errno == EINTR)
		f = NULL;
# else
	    f = fopen((char *) __stringVal(path), (char *) __stringVal(openmode));
# endif
#endif
	    /* must refetch - could be GC'd */
	    path = __INST(pathName);
	} while ((f == NULL) && (errno == EINTR));
	__END_INTERRUPTABLE__

	if (f == NULL) {
	    /*
	     * If no filedescriptors available, try to finalize
	     * possibly collected fd's and try again.
	     */
	    if (pass == 0 && (errno == ENFILE || errno == EMFILE)) {
		pass = 1;
		__SSEND0(@global(ObjectMemory), @symbol(scavenge), 0);
		__SSEND0(@global(ObjectMemory), @symbol(finalize), 0);
		goto retry;
	    }
	getOutOfHere: ;
	    __INST(lastErrorNumber) = __MKSMALLINT(errno);
	    __INST(position) = nil;
	} else {
#ifdef __VMS__
	    /*
	     * check to see if this is positionable ...
	     */
	    __INST(canPosition) = false;
# ifndef _POSIX_C_SOURCE
	    {
		struct stat statBuffer;

		if (fstat(fileno(f), &statBuffer) >= 0) {
		    switch (statBuffer.st_fab_rfm) {
                        case FAB$C_UDF: /* undefined (also stream binary)   */
                        case FAB$C_VAR: /* variable length records          */
                        case FAB$C_VFC: /* variable fixed control           */
                        case FAB$C_STM: /* RMS-11 stream (valid only for sequen> */
                        default:
			    __INST(canPosition) = false;
			    break;

                        case FAB$C_FIX: /* fixed length records             */
                        case FAB$C_STMLF: /* LF stream (valid only for sequential> */
                        case FAB$C_STMCR: /* CR stream (valid only for sequential> */
			    __INST(canPosition) = true;
                            break;
		    }
		}
	    }
# endif 
#else /* not VMS */
	    __INST(canPosition) = true;
#endif /* poor VMS */

	    __INST(filePointer) = fp = __MKOBJ((INT)f); __STORE(self, fp);
	    __INST(position) = __MKSMALLINT(1);
	    ok = true;
	}
    }
%}.
    ok ifFalse:[
	"
	 the open failed for some reason ...
	"
	^ self openError
    ].
    buffered := true.       "default is buffered"
    Lobby register:self.
!

pathName:filename
    "set the pathname"

    pathName := filename
!

pathName:filename in:aDirectory
    "set the pathname starting at aDirectory, a FileDirectory"

    pathName := aDirectory pathName asFilename constructString:filename
!

reOpen
    "sent after snapin to reopen streams"

    |oldPos|

    filePointer notNil ifTrue:[
	"it was open, when snapped-out"
	filePointer := nil.
	Lobby unregister:self.
	oldPos := position.
	self open.
	filePointer isNil ifTrue:[
	    "/ this happens, if after a restart, 
	    "/ the file is no longer present or accessable ..."

	    (self class name , ' [warning]: could not reOpen file: ', pathName) errorPrintCR.
	] ifFalse:[
	    self position:oldPos.
	]
    ]

    "Modified: 10.1.1997 / 17:50:51 / cg"
!

setMode:aModeSymbol
    mode := aModeSymbol
! !

!FileStream methodsFor:'queries'!

fileSize
    "return the size in bytes of the file"

%{  /* NOCONTEXT */

#ifdef transputer
    FILE *f;
    int size;

    if (__INST(filePointer) != nil) {
	f = __FILEVal(__INST(filePointer));
	if ((size = filesize(fileno(f))) >= 0) {
	    RETURN ( __MKSMALLINT(size) );
	}
    }
#else
    FILE *f;
    struct stat buf;
    int ret;
    int fd;

    if (__INST(filePointer) != nil) {
	f = __FILEVal(__INST(filePointer));
	fd = fileno(f);
	do {
	    ret = fstat(fd, &buf);
	} while ((ret < 0) && (errno == EINTR));
	if (ret >= 0) {
	    RETURN ( __MKSMALLINT(buf.st_size) );
	}
	__INST(lastErrorNumber) = __MKSMALLINT(errno);
    }
#endif
%}.

    "could add a fall-back here:

	oldPosition := self position.
	self setToEnd.
	sz := self position.
	self position:oldPosition.
	^ sz
    "
    lastErrorNumber notNil ifTrue:[^ self ioError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ self primitiveFailed
!

size
    "return the size of the stream;
     thats the number of bytes of the file."

    "/ no obsoleteMethodWarning - size is ok for streams.
    "/ self obsoleteMethodWarning:'use #fileSize'.

    ^ self fileSize.

    "Modified: 4.10.1997 / 18:01:09 / cg"
! !

!FileStream methodsFor:'testing'!

isFileStream
    "return true, if the receiver is some kind of fileStream.
     redefined from Object"

    ^ true
! !

!FileStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/FileStream.st,v 1.50 1997-10-04 17:01:30 cg Exp $'
! !
FileStream initialize!