FileStream.st
author Claus Gittinger <cg@exept.de>
Thu, 05 Feb 2004 12:57:29 +0100
changeset 7872 634e73a5cdd9
parent 7871 5c357f1ba0c9
child 7874 5e0319ca5e60
permissions -rw-r--r--
preps for 64bit positions

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

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

"{ Package: 'stx:libbasic' }"

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

!FileStream primitiveDefinitions!
%{

#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 /* not transputer */

# include <sys/types.h>
# include <sys/stat.h>

#endif /* not transputer */

#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();
# ifndef FREEBSD
  extern long lseek();
# endif
# define HFILE FILE *

#endif

#ifdef WIN32
# define NO_STDIO
# ifdef i386
#  define _X86_
# endif

# undef INT
# undef Array
# undef Number
# undef Method
# undef Point
# undef Rectangle
# undef Block
# undef Time
# undef Date
# undef Set
# undef Signal
# undef Delay
# undef Context

# define NOATOM
# define NOGDICAPMASKS
# define NOMETAFILE
# define NOMINMAX
//# define NOOPENFILE
# define NOSOUND
# define NOWH
//# define NOCOMM
# define NOKANJI
# define NOCRYPT
//# define NOMCX
# define WIN32_LEAN_AND_MEAN

# include <windows.h>
# include <winsock.h> /* */
# include <io.h>

# if !defined(__BORLANDC__)
#  define stat _stat
# endif

# ifdef __DEF_Array
#  define Array __DEF_Array
# endif
# ifdef __DEF_Number
#  define Number __DEF_Number
# endif
# ifdef __DEF_Method
#  define Method __DEF_Method
# endif
# ifdef __DEF_Point
#  define Point __DEF_Point
# endif
# ifdef __DEF_Block
#  define Block __DEF_Block
# endif
# ifdef __DEF_Time
#  define Time __DEF_Time
# endif
# ifdef __DEF_Date
#  define Date __DEF_Date
# endif
# ifdef __DEF_Set
#  define Set __DEF_Set
# endif
# ifdef __DEF_Signal
#  define Signal __DEF_Signal
# endif
# ifdef __DEF_Delay
#  define Delay __DEF_Delay
# endif
# ifdef __DEF_Context
#  define Context __DEF_Context
# endif

# define INT int

# ifndef DO_WRAP_CALLS
#  define STX_C_CALL0(__nm__, __f__)                            __f__((__a1__))
#  define STX_C_CALL1(__nm__, __f__, __a1__)                    __f__((__a1__))
#  define STX_C_CALL2(__nm__, __f__, __a1__, __a2__)            __f__((__a1__), (__a2__))
#  define STX_C_CALL3(__nm__, __f__, __a1__, __a2__, __a3__)    __f__((__a1__), (__a2__), (__a3__))
# else
#  define STX_C_CALL0(__nm__, __f__)                            __STX_C_CALL0(__nm__, (void*)__f__)
#  define STX_C_CALL1(__nm__, __f__, __a1__)                    __STX_C_CALL1(__nm__, (void*)__f__, (void*)(__a1__))
#  define STX_C_CALL2(__nm__, __f__, __a1__, __a2__)            __STX_C_CALL2(__nm__, (void*)__f__, (void*)(__a1__), (void*)(__a2__))
#  define STX_C_CALL3(__nm__, __f__, __a1__, __a2__, __a3__)    __STX_C_CALL3(__nm__, (void*)__f__, (void*)(__a1__), (void*)(__a2__), (void*)(__a3__))
# endif

/* #  define HFILE HANDLE */
#  define HFILE FILE *
/* #  define fileno(f) f */

// extern long lseek();


#endif /* WIN32 */

#include "stxOSDefs.h"

/*
 * 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
    UserInitiatedFileSaveQuerySignal 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.
        "/ THE FUTURE IS NOW!!!!
        "/
"/        OpenErrorSignal := QuerySignal new.
"/        OpenErrorSignal parent:(super openErrorSignal) mayProceed:true.
"/        OpenErrorSignal nameClass:self message:#openErrorSignal.
"/        OpenErrorSignal notifierString:'open error'.

        UserInitiatedFileSaveQuerySignal := QuerySignal new defaultAnswer:true.
        UserInitiatedFileSaveQuerySignal nameClass:self message:#userInitiatedFileSaveQuerySignal.
    ]

    "Modified: 8.10.1997 / 11:56:39 / cg"
! !

!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

    "
     FileStream appendingOldFileNamed:'adasdasasd'
    "
!

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

    [
        ^ self oldFileNamed:filename.
    ] on:self openErrorSignal do:[:ex| ].

    ^ self newFileNamed:filename
!

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

    [
        ^ self oldFileNamed:filename in:aDirectory.
    ] on:self openErrorSignal do:[:ex| ].

    ^ self newFileNamed:filename in:aDirectory
!

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

    "Modified: / 28.10.1997 / 14:28:08 / cg"
!

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.
     Raises an error if the file does not exist."

    |newStream|

"/ We can do the following, but is is an extra OS-systemcall:
"/    (OperatingSystem isReadable:filename) ifFalse:[^ self new openError].

    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

    "
     FileStream oldFileNamed:'/dAsGiBtEsNiChT'
    "
!

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.
     Raises an error if the file does not exist."

    |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

    "
     FileStream oldFileNamed:'dAsGiBtEsNiChT' in:'/'
    "
!

readonlyFileNamed:filename
    "return a readonly FileStream for existing file named filename, aString.
     Raises an error if the file does not exist."

    |newStream|

"/ We can do the following, but is is an extra OS-systemcall:
"/    (OperatingSystem isReadable:filename) ifFalse:[^ self new openError].

    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

    "
     FileStream readonlyFileNamed:'dAsGiBtEsNiChT' 
    "
!

readonlyFileNamed:filename in:aDirectory
    "return a readonly FileStream for existing file named filename, aString
     in aDirectory, a fileName or string instance representing a directory.
     Raises an error if the file does not exist."

    |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 readonlyFileNamed:'dAsGiBtEsNiChT' in:'/'
     FileStream readonlyFileNamed:'dAsGiBtEsNiChT' in:'/' asFilename
    "
! !

!FileStream class methodsFor:'Compatibility-ANSI'!

write: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.
     Same as newFileNamed: for ANSI compatibilily"

    ^ self newFileNamed:filename
! !

!FileStream class methodsFor:'Compatibility-Dolphin'!

read:filename text:text
    "return a readonly FileStream for the existing file named filename, aString.
     If the argument, text is false, the stream is setup to read binary bytes,
     if false, it reads characters."

    |s|

    s := self readOnlyFileNamed:filename.
    text ifTrue:[
	s text
    ] ifFalse:[
	s binary
    ].
    ^ s
!

write:filename mode:modeSymbol
    "return a writable FileStream for the file named filename, aString.
     The modeSymbol controls how the file is opened; currently supported are:
        #append
    "

    modeSymbol == #append ifTrue:[
        ^ self appendingOldFileNamed:filename
    ].
    "/ self openErrorSignal is a Notification. This will change..
    "/ We want to raise a real error here
    super openErrorSignal raiseRequestErrorString:' - unsupported mode'.
    ^ nil
!

write:filename text:textModeBoolean
    "return a writable FileStream for the file named filename, aString.
     If the argument, text is false, the stream is setup to write binary bytes,
     if false, it writes characters."

    |s|

    s := self newFileNamed:filename.
    s notNil ifTrue:[
	textModeBoolean ifTrue:[
	    s text
	] ifFalse:[
	    s binary
	]
    ].
    ^ s
! !

!FileStream class methodsFor:'Compatibility-Squeak'!

readOnlyFileNamed:filename
    "return a readonly FileStream for the existing file named filename, aString."

    ^ self readonlyFileNamed:filename
! !

!FileStream class methodsFor:'Compatibility-VW'!

badArgumentsSignal
    ^ Error
! !

!FileStream class methodsFor:'Signal constants'!

userInitiatedFileSaveQuerySignal
    "return the query signal, which is raised before a user-initiated
     file-save / file-saveAs operation is performed.
     The query will be invoked with the fileName which is about to be
     written to.
     The default signal here returnes true, which will grant the save.
     End-user applications may want to catch this signal,
     and only return true for certain directories."

    ^ UserInitiatedFileSaveQuerySignal

! !

!FileStream methodsFor:'Compatibility-Squeak'!

fullName
    "Squeak compatibility: return the full pathname"

    ^ pathName asFilename pathName

    "Created: 17.10.1997 / 17:04:12 / cg"
    "Modified: 20.10.1997 / 19:22:44 / cg"
! !

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

removeOnClose:aBoolean
    "set/clear the removeOnClose flag.
     If set, the file will be removed when closed.
     Provided mostly for OS's which do not allow an
     open file to be removed (i.e. non unixes),
     and a fileStream for a tempFile is used.
     Especially, the CVS-SourceCodeManager returns
     this kind of file-handles occasionally.
     This is an ST/X special feature which is not portable
     to other systems."

    removeOnClose := aBoolean

    "Modified: / 13.8.1998 / 12:10:07 / cg"
!

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"

    "/ This has changed from previous releases:
    "/ in earlier versions of ST/X, failed file open operations
    "/ returned nil - now, an error is raised.
    "/ The old behavior is simulated by providing an exception
    "/ handler, which proceeds with nil.
    "/
    "/ Sorry about that.
    "/
    LastErrorNumber := lastErrorNumber.
    ^ super openError.

    "
     '/dasGIBtEsbeStimmtNiChT' asFilename readStream
    "
! !

!FileStream methodsFor:'instance release'!

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

    super closeFile.
    removeOnClose == true ifTrue:[
	pathName asFilename remove.
    ]

    "Created: / 13.8.1998 / 12:11:22 / cg"
! !

!FileStream methodsFor:'positioning'!

position0Based
    "return the read/write position in the file"

%{

    HFILE f;
    off_t currentPosition;

    if (__INST(filePointer) != nil) {
        do {
            f = __FILEVal(__INST(filePointer));
#ifdef WIN32
            __threadErrno = 0;
            if (__INST(buffered) == true) {                             
# if 0
                currentPosition = STX_C_CALL1( "ftell", ftell, f);     
# else
                currentPosition = ftell(f);     
# endif
            } else {                                                   
                OBJ rA = __INST(readAhead);                            
                long offs = 0L;

                if (rA != nil) {                                       
                    __INST(readAhead) = nil;                           
                    offs = -1L;
                }                                                      
# if 0
                currentPosition = STX_C_CALL3( "lseek", lseek, fileno(f), offs, SEEK_CUR); 
# else
                currentPosition = lseek(fileno(f), offs, SEEK_CUR); 
# endif
            }
#else
            if (__INST(buffered) == true) {
                currentPosition = ftell(f);
            } else {
                currentPosition = lseek(fileno(f), 0L, SEEK_CUR);
            }
#endif
        } while ((currentPosition < 0) && (__threadErrno == EINTR));

        if (currentPosition >= 0) {
            OBJ rslt;

            if (sizeof(currentPosition) == 8) {
                rslt = __MKINT64 (&currentPosition);
            } else {
                rslt = __MKINT(currentPosition);
            }
            RETURN ( rslt );
        }
        __INST(lastErrorNumber) = __MKSMALLINT(__threadErrno);
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self ioError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ self primitiveFailed
!

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

    |rslt|
%{

    HFILE f;
    long ret;
    OBJ fp;

    if ((__INST(canPosition) != false) 
     || (newPos == __MKSMALLINT(0))) {
        if ((fp = __INST(filePointer)) != nil) {
            long nP;
            __int64__ nP64;
            int need64BitPosition = 0;

            if (__isSmallInteger(newPos)) {
                nP = __intVal(newPos);
                if (nP < 0) {
                    __INST(lastErrorNumber) = __MKSMALLINT(EINVAL);
                    goto getOutOfHere;
                }
            } else {
                nP = __signedLongIntVal(newPos);
                if (nP < 0) {
                    __INST(lastErrorNumber) = __MKSMALLINT(EINVAL);
                    goto getOutOfHere;
                }
                if (nP == 0) {
                    __int64__ nP64;

                    if (__signedLong64IntVal(newPos, &nP64) == 0) {
                        __INST(lastErrorNumber) = __MKSMALLINT(EINVAL);
                        goto getOutOfHere;
                    }
                    if (nP64.hi < 0) {
                        __INST(lastErrorNumber) = __MKSMALLINT(EINVAL);
                        goto getOutOfHere;
                    }
                    need64BitPosition = 1;
                }
            }

            f = __FILEVal(fp);

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

    rslt := self positionFile:filePointer position0Based:newPos.
    rslt >= 0 ifTrue:[
        position := newPos.
    ] ifFalse:[
        hitEOF := true.
    ]
!

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

%{
    HFILE f;
    long ret;

    if (__INST(filePointer) != nil) {
	f = __FILEVal(__INST(filePointer));
	__INST(position) = nil;    /* i.e. unknown */
	do {
#ifdef WIN32
	    __threadErrno = 0;
	    if (__INST(buffered) == true) {                                            
		ret = STX_C_CALL3( "fseek", fseek, f, 0L, SEEK_END);    
	    } else {                                                   
		__INST(readAhead) = nil;                           
		ret = STX_C_CALL3( "lseek", lseek, fileno(f), 0L, SEEK_END);
	    }
#else
	    if (__INST(buffered) == true) {
		ret = fseek(f, 0L, SEEK_END);
	    } else {
		ret = lseek(fileno(f), 0L, SEEK_END);
	    }
#endif
	} while ((ret < 0) && (__threadErrno == EINTR));
	if (ret >= 0) {
	    RETURN ( self );
	}
	__INST(lastErrorNumber) = __MKSMALLINT(__threadErrno);
    }
%}.
    lastErrorNumber notNil ifTrue:[^ self ioError].
    filePointer isNil ifTrue:[^ self errorNotOpen].
    ^ self primitiveFailed
!

slowPosition0Based: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 pos0Based|

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

    buffer := ByteArray new:8*1024.

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

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

    ^ self slowPosition0Based:(newPos - ZeroPosition)
! !

!FileStream methodsFor:'printing & storing'!

printOn:aStream
    "append a user printed representation of the receiver to aStream.
     The format is suitable for a human - not meant to be read back."

    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 ~~ ZeroPosition) 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 attributes:nil
!

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
!

openFile:pathName withMode: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."

    |filePointer|

%{
    HFILE f;
    HFILE fopen();
    OBJ fp;
    int pass = 0;

retry:
    if (__isNonNilObject(pathName) && (__qClass(pathName)==String)) {
#ifdef __VMS__
	do {
	    /*
	     * allow passing additional RMS arguments.
	     * stupid: DEC does not seem to offer an interface for passing a char **.
	     */
	    __threadErrno = 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;
			    __threadErrno = EINVAL; /* invalid argument */
			    goto getOutOfHere;
			}
		    }
		    switch (numAttrib) {
			case 0:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode));
			    __END_INTERRUPTABLE__
			    break;
			case 1:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode),
				      __stringVal(ap[0]));
			    __END_INTERRUPTABLE__
			    break;
			case 2:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]));
			    __END_INTERRUPTABLE__
			    break;
			case 3:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]));
			    __END_INTERRUPTABLE__
			    break;
			case 4:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]));
			    __END_INTERRUPTABLE__
			    break;
			case 5:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]));
			    __END_INTERRUPTABLE__
			    break;
			case 6:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]), __stringVal(ap[5]));
			    __END_INTERRUPTABLE__
			    break;
			case 7:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode),
				      __stringVal(ap[0]), __stringVal(ap[1]), __stringVal(ap[2]),
				      __stringVal(ap[3]), __stringVal(ap[4]), __stringVal(ap[5]),
				      __stringVal(ap[6]));
			    __END_INTERRUPTABLE__
			    break;
			case 8:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (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]));
			    __END_INTERRUPTABLE__
			    break;
			case 9:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (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]));
			    __END_INTERRUPTABLE__
			    break;
			case 10:
			    __BEGIN_INTERRUPTABLE__
			    f = fopen((char *)__stringVal(pathName), (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]));
			    __END_INTERRUPTABLE__
			    break;
			default:
			    f = NULL;
			    __threadErrno = E2BIG; /* too many args */
			    goto getOutOfHere;
		    }
		} else if (attributeSpec != nil) {
		    f = NULL;
		    __threadErrno = EINVAL; /* invalid argument */
		    goto getOutOfHere;
		} else {
		    /*
		     * create file as sequential streamLF by default.
		     */
		    __BEGIN_INTERRUPTABLE__
		    f = fopen((char *)__stringVal(pathName), (char *)__stringVal(openmode), "rfm=stmlf");
		    __END_INTERRUPTABLE__
		}
	    }
	} while ((f == NULL) && (__threadErrno == EINTR));

#else /* not VMS */

# ifdef WIN32

	do {
	    __threadErrno = 0;
	    f = STX_C_CALL2( "fopen", fopen, (char *)__stringVal(pathName), (char *)__stringVal(openmode));
	    if (__threadErrno == EINTR) {
		f = NULL;
	    }
	} while ((f == NULL) && (__threadErrno == EINTR));

# else /* not WIN32 */

	do {
	    __BEGIN_INTERRUPTABLE__
#  ifdef LINUX
	    /* 
	     * LINUX may ret a non-NULL f even when interrupted.
	     * Therefore, check errno and fake a null-ret.
	     */
	    __threadErrno = 0;
	    f = fopen((char *) __stringVal(pathName), (char *) __stringVal(openmode));
	    if (__threadErrno == EINTR)
		f = NULL;
#  else /* not LINUX */
	    f = fopen((char *) __stringVal(pathName), (char *) __stringVal(openmode));
#  endif /* not LINUX */
	    __END_INTERRUPTABLE__
	} while ((f == NULL) && (__threadErrno == EINTR));

# endif /* not WIN32 */
#endif /* not VMS */

	if (f == NULL) {
	    /*
	     * If no filedescriptors available, try to finalize
	     * possibly collected fd's and try again.
	     */
	    if (pass == 0 && (__threadErrno == ENFILE || __threadErrno == EMFILE)) {
		pass = 1;
		__SSEND0(@global(ObjectMemory), @symbol(scavenge), 0);
		__SSEND0(@global(ObjectMemory), @symbol(finalize), 0);
		goto retry;
	    }
	getOutOfHere: ;
	    __INST(lastErrorNumber) = __MKSMALLINT(__threadErrno);
	    __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 */

	    if (@global(FileOpenTrace) == true) {
		fprintf(stderr, "fopen %s [FileStream] -> %x\n", __stringVal(pathName), f);
	    }

	    filePointer = __MKOBJ((INT)f); 
	    __INST(position) = @global(PositionableStream:ZeroPosition);
	}
    }
%}.
    ^ filePointer
!

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

    filePointer notNil ifTrue:[^ self errorAlreadyOpen].

    filePointer := self openFile:pathName withMode:openmode attributes:attributeSpec.
    filePointer isNil ifTrue:[
	"
	 the open failed for some reason ...
	"
	^ self openError
    ].
    position := ZeroPosition.
    buffered := true.       "default is buffered"
    Lobby register:self.
!

pathName:filename
    "set the pathname"

    pathName := filename asString

    "Modified: / 28.10.1997 / 14:29:01 / cg"
!

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

    pathName := aDirectory asFilename constructString:filename

    "Modified: / 28.10.1997 / 14:28:54 / cg"
!

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:[
	    oldPos notNil ifTrue:[
		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"

%{

    HFILE f;

#ifdef transputer
    int size;

    if (__INST(filePointer) != nil) {
	f = __FILEVal(__INST(filePointer));
	if ((size = filesize(fileno(f))) >= 0) {
	    RETURN ( __MKSMALLINT(size) );
	}
    }
#else
    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) && (__threadErrno == EINTR));
	if (ret >= 0) {
	    RETURN ( __MKSMALLINT( (int)(buf.st_size) ) );
	}
	__INST(lastErrorNumber) = __MKSMALLINT(__threadErrno);
    }
#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:'rel5 protocol'!

positionFile:filePointer position:newPos
    "for migration to rel5 only"

    self primitiveFailed
! !

!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.100 2004-02-05 11:57:29 cg Exp $'
! !

FileStream initialize!