AbstractOperatingSystem.st
author Claus Gittinger <cg@exept.de>
Tue, 11 Dec 2001 16:07:01 +0100
changeset 6278 ca32319d98b2
parent 6162 5bd760d061c4
child 6279 e3ae1abe60bc
permissions -rw-r--r--
error text handling

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

"{ Package: 'stx:libbasic' }"

Object subclass:#AbstractOperatingSystem
	instanceVariableNames:''
	classVariableNames:'ConcreteClass LastErrorNumber LocaleInfo OSSignals PipeFailed
		ErrorSignal AccessDeniedErrorSignal FileNotFoundErrorSignal
		InvalidArgumentsSignal UnsupportedOperationSignal Resources'
	poolDictionaries:''
	category:'System-Support'
!

!AbstractOperatingSystem class methodsFor:'documentation'!

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

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

documentation
"
    this class realizes services common to the supported operating systems;
    typically, services which can be implemented based upon more primitive
    functions, or which can be implemented in a portable way (but probably
    less performant) are implemented here.

    [Class variables:]
        ConcreteClass   <Class>         the real OS class

        LocaleInfo      <Dictionary>    if non nil, that is taken instead of the operating
                                        systems locale definitions (allows for overwriting
                                        these, or provide a compatible info on systems which do
                                        not support locales)

        LastErrorNumber <Integer>       the last value of errno

        OSSignals       <Array>         Array of signals to be raised for corresponding
                                        OperatingSystem signals.

        PipeFailed      <Boolean>       set if a fork (or popen) has failed;
                                        ST/X will avoid doing more forks/popens
                                        if this flag is set, for a slightly
                                        smoother operation.

        ErrorSignal     <Signal>        Parentsignal of all OS error signals.
                                        not directly raised.

        AccessDeniedErrorSignal         misc concrete error reporting signals
        FileNotFoundErrorSignal
        UnsupportedOperationSignal
        InvalidArgumentsSignal

    [author:]
        Claus Gittinger

    [see also:]
        OSProcessStatus
        Filename Date Time
        ExternalStream FileStream PipeStream Socket
"
!

examples
"
  various queries
                                                                [exBegin]
    Transcript 
        showCR:'hello ' , (OperatingSystem getLoginName)
                                                                [exEnd]

                                                                [exBegin]
    OperatingSystem isUNIXlike ifTrue:[
        Transcript showCR:'this is some UNIX-like OS'
    ] ifFalse:[
        Transcript showCR:'this OS is not UNIX-like'
    ]
                                                                [exEnd]

                                                                [exBegin]
    Transcript 
        showCR:'this machine is called ' , OperatingSystem getHostName
                                                                [exEnd]

                                                                [exBegin]
    Transcript 
        showCR:('this machine is in the '
               , OperatingSystem getDomainName
               , ' domain')
                                                                [exEnd]

                                                                [exBegin]
    Transcript 
        showCR:('this machine''s CPU is a '
               , OperatingSystem getCPUType
               )
                                                                [exEnd]

                                                                [exBegin]
    Transcript showCR:'executing ls command ...'.
    OperatingSystem executeCommand:'ls'.
    Transcript showCR:'... done.'.
                                                                [exEnd]

  locking a file 
  (should be executed on two running smalltalks - not in two threads):
                                                                [exBegin]
    |f|

    f := 'testFile' asFilename readWriteStream.

    10 timesRepeat:[
        'about to lock ...' printCR.
        [
          OperatingSystem 
            lockFD:(f fileDescriptor)
            shared:false
            blocking:false
        ] whileFalse:[
            'process ' print. OperatingSystem getProcessId print. ' is waiting' printCR.
            Delay waitForSeconds:1
        ].
        'LOCKED ...' printCR.
        Delay waitForSeconds:10.
        'unlock ...' printCR.
        (OperatingSystem 
            unlockFD:(f fileDescriptor)) printCR.
        Delay waitForSeconds:3.
    ]
                                                                [exBegin]
"
! !

!AbstractOperatingSystem class methodsFor:'initialization'!

initResources
    Resources := ResourcePack for:self
!

initialize
    "initialize the class"

    self initializeConcreteClass.

    ErrorSignal isNil ifTrue:[
        ErrorSignal := Object errorSignal newSignalMayProceed:true.
        ErrorSignal nameClass:self message:#errorSignal.
        ErrorSignal notifierString:'OS error encountered'.

        AccessDeniedErrorSignal := ErrorSignal newSignalMayProceed:true.
        AccessDeniedErrorSignal nameClass:self message:#accessDeniedError.
        AccessDeniedErrorSignal notifierString:'OS access denied'.

        FileNotFoundErrorSignal := ErrorSignal newSignalMayProceed:true.
        FileNotFoundErrorSignal nameClass:self message:#fileNotFoundErrorSignal.
        FileNotFoundErrorSignal notifierString:'OS file not found'.

        InvalidArgumentsSignal := ErrorSignal newSignalMayProceed:true.
        InvalidArgumentsSignal nameClass:self message:#invalidArgumentsSignal.
        InvalidArgumentsSignal notifierString:'bad arg to OS call'.

        UnsupportedOperationSignal := ErrorSignal newSignalMayProceed:true.
        UnsupportedOperationSignal nameClass:self message:#unsupportedOperationSignal.
        UnsupportedOperationSignal notifierString:'operation not supported by this OS'.
    ].
    Smalltalk addDependent:self.    "/ to catch language changes
!

initializeConcreteClass
    |osType cls|

    osType := self getSystemType.
    osType = 'win32' ifTrue:[
        cls := Win32OperatingSystem
    ] ifFalse:[
        osType = 'os2' ifTrue:[
            cls := OS2OperatingSystem
        ] ifFalse:[
            osType = 'macos' ifTrue:[
                cls := MacOperatingSystem
            ] ifFalse:[
                ((osType = 'VMS') or:[osType = 'openVMS']) ifTrue:[
                    cls := OpenVMSOperatingSystem
                ] ifFalse:[
                    cls := UnixOperatingSystem
                ]
            ]
        ]
    ].
    OperatingSystem := ConcreteClass := cls.
! !

!AbstractOperatingSystem class methodsFor:'OS signal constants'!

sigABRT
    "return the signal number for SIGABRT - 0 if not supported by OS
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigALRM
    "return the signal number for SIGALRM - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigBREAK
    "return the signal number for SIGBREAK - 0 if not supported.
     This is an MSDOS specific signal"

    ^ 0
!

sigBUS
    "return the signal number for SIGBUS - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigCHLD
    "return the signal number for SIGCHLD - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigCONT
    "return the signal number for SIGCONT - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigDANGER
    "return the signal number for SIGDANGER - 0 if not supported
     (seems to be an AIX special)"

    ^ 0
!

sigEMT
    "return the signal number for SIGEMT - 0 if not supported by OS
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigFP
    "return the signal number for SIGFP - 0 if not supported by OS
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigGRANT
    "return the signal number for SIGGRANT - 0 if not supported
     (seems to be an AIX special)"

    ^ 0
!

sigHUP
    "return the signal number for SIGHUP
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigILL
    "return the signal number for SIGILL - 0 if not supported by OS
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigINT
    "return the signal number for SIGINT
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigIO
    "return the signal number for SIGIO - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigIOT
    "return the signal number for SIGIOT - 0 if not supported by OS
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigKILL
    "return the signal number for SIGKILL
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigLOST
    "return the signal number for SIGLOST - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigMIGRATE
    "return the signal number for SIGMIGRATE - 0 if not supported
     (seems to be an AIX special)"

    ^ 0
!

sigMSG
    "return the signal number for SIGMSG - 0 if not supported
     (seems to be an AIX special)"

    ^ 0
!

sigPIPE
    "return the signal number for SIGPIPE - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigPOLL
    "return the signal number for SIGPOLL - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigPRE
    "return the signal number for SIGPRE - 0 if not supported
     (seems to be an AIX special)"

    ^ 0
!

sigPROF
    "return the signal number for SIGPROF - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigPWR
    "return the signal number for SIGPWR - 0 if not supported
     (not available on all systems)"

    ^ 0
!

sigQUIT
    "return the signal number for SIGQUIT
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigRETRACT
    "return the signal number for SIGRETRACT - 0 if not supported
     (seems to be an AIX special)"

    ^ 0
!

sigSAK
    "return the signal number for SIGSAK - 0 if not supported
     (seems to be an AIX special)"

    ^ 0
!

sigSEGV
    "return the signal number for SIGSEGV - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigSOUND
    "return the signal number for SIGSOUND - 0 if not supported
     (seems to be an AIX special)"

    ^ 0
!

sigSTOP
    "return the signal number for SIGSTOP - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigSYS
    "return the signal number for SIGSYS - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigTERM
    "return the signal number for SIGTERM - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigTRAP
    "return the signal number for SIGTRAP - 0 if not supported by OS
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigTSTP
    "return the signal number for SIGTSTP - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigTTIN
    "return the signal number for SIGTTIN - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigTTOU
    "return the signal number for SIGTTOU - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigURG
    "return the signal number for SIGURG - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigUSR1
    "return the signal number for SIGUSR1 - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigUSR2
    "return the signal number for SIGUSR2 - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigVTALRM
    "return the signal number for SIGVTALRM - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigWINCH
    "return the signal number for SIGWINCH - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigXCPU
    "return the signal number for SIGXCPU - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
!

sigXFSZ
    "return the signal number for SIGXFSZ - 0 if not supported
     (the numeric value is not the same across unix-systems)"

    ^ 0
! !

!AbstractOperatingSystem class methodsFor:'Signal constants'!

accessDeniedErrorSignal
    "return the signal raised when a (file-) access is denied."

    ^ AccessDeniedErrorSignal
!

errorSignal
    "return the parent signal of all OS signals."

    ^ ErrorSignal

    "Modified: 22.4.1996 / 13:11:31 / cg"
!

fileNotFoundErrorSignal
    "return the signal raised when a file was not found."

    ^ FileNotFoundErrorSignal
!

invalidArgumentsSignal
    "return the signal which is raised for invalid arguments.
     Currently, this is never raised."

    ^ InvalidArgumentsSignal

    "Created: 13.9.1997 / 10:46:47 / cg"
    "Modified: 13.9.1997 / 10:47:03 / cg"
!

unsupportedOperationSignal
    "return the signal which is raised when an operation
     is attempted, which is not supported by the OS.
     (For example, creating a link on VMS or MSDOS)"

    ^ UnsupportedOperationSignal
! !

!AbstractOperatingSystem class methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    ((something == #Language) or:[something == #LanguageTerritory]) ifTrue:[
        self initResources
    ]
! !

!AbstractOperatingSystem class methodsFor:'error messages'!

clearLastErrorNumber
    "return the last errors number.
     See also: #lastErrorSymbol and #lastErrorString.
     Notice: having a single error number is a bad idea in a multithreaded
             environment - this interface will change."

    LastErrorNumber := nil.

     "
      AbstractOperatingSystem clearLastErrorNumber
     "

    "Created: 12.4.1996 / 09:28:58 / stefan"
    "Modified: 12.4.1996 / 09:38:51 / stefan"
!

currentErrorNumber
    "returns the OS's last error nr (i.e. the value of errno).
     Notice, that the value of this flag is only valid immediately
     after the error occurred - it gets updated with every other
     request to the OS.
     Use lastErrorNumber - currentErrorNumber is invalidated by
     many, many internal calls."

    ^ self lastErrorNumber

     "
      OperatingSystem currentErrorNumber
     "
!

errorNumberFor:aSymbol
    "given a symbolic error, return the numeric;
     (i.e. errorNumberFor:#EBADF returns EBADF's value).
     Use this, since error numbers are really not standard across unix systems."

    ^ -1
!

errorStringForSymbol:errorSymbol
    "return an errorMessage for an errorSymbol
     (as kept in an osErrorHolder)."

    Resources isNil ifTrue:[
        ^ errorSymbol
    ].
    ^ Resources at:errorSymbol ifAbsent:errorSymbol

    "
     OperatingSystem errorStringForSymbol:#EPERM
     OperatingSystem errorStringForSymbol:(OperatingSystem errorSymbolForNumber:4)
    "
!

errorSymbolAndTextForNumber:errNr
    "return an array consisting of symbol &  message string from a unix errorNumber 
     (as returned by a system call). 
     The returned message is in english (as found in /usr/include/errno.h)
     and should be replaced by a resource lookup before being presented to the user."

    ^ Array 
        with:#'ERROR_OTHER' 
        with:('ErrorNr: ' , errNr printString)

    "
     OperatingSystem errorSymbolAndTextForNumber:4
    "
!

errorSymbolForNumber:errNr
    "return a symbol for a unix errorNumber
     (as returned by a system call)."

    ^ (self errorSymbolAndTextForNumber:errNr) at:1

    "
     OperatingSystem errorSymbolForNumber:4
     OperatingSystem errorSymbolForNumber:2
    "

    "Modified: 12.4.1996 / 09:16:29 / stefan"
    "Modified: 13.9.1996 / 16:23:35 / cg"
!

errorTextForNumber:errNr
    "return a message string from a unix errorNumber 
     (as returned by a system call). 
     The returned message is in english (as found in /usr/include/errno.h)
     and should be replaced by a resource lookup before being presented to the user."

    ^ (self errorSymbolAndTextForNumber:errNr) at:2

    "
     OperatingSystem errorTextForNumber:4
    "
!

lastErrorNumber
    "return the last errors number.
     See also: #lastErrorSymbol and #lastErrorString.
     Notice: having a single error number is a bad idea in a multithreaded
             environment - this interface will change."

    ^ LastErrorNumber

     "
      OperatingSystem lastErrorNumber
     "
!

lastErrorString
    "return a message string describing the last error.
     See also: #lastErrorNumber and #lastErrorSymbol.
     Notice: having a single error number is a bad idea in a multithreaded
             environment - this interface will change."

    LastErrorNumber isNil ifTrue:[^ nil].
    ^ self errorTextForNumber:LastErrorNumber

    "
     OperatingSystem lastErrorString
    "
!

lastErrorSymbol
    "return a symbol (such as #EBADF or #EACCESS) describing the last error.
     See also: #lastErrorNumber and #lastErrorString.
     Notice: having a single error number is a bad idea in a multithreaded
             environment - this interface will change."

    LastErrorNumber isNil ifTrue:[^ nil].
    ^ self errorSymbolForNumber:LastErrorNumber

    "
     OperatingSystem lastErrorSymbol
    "
! !

!AbstractOperatingSystem class methodsFor:'executing OS commands'!

canExecuteCommand:aCommandString
    "return true, if the OS can execute aCommand.
     For now, this only works with UNIX."

    |cmd|

    cmd := aCommandString asCollectionOfWords first.
    ^ (self pathOfCommand:cmd) notNil

    "
     OperatingSystem canExecuteCommand:'fooBar'  
     OperatingSystem canExecuteCommand:'ls'  
     OperatingSystem canExecuteCommand:'cvs'  
    "

    "Created: 4.11.1995 / 19:13:54 / cg"
!

commandAndArgsForOSCommand:aCommandString
    "get a shell and shell arguments for command execution"

    self subclassResponsibility
!

exec:aCommandPath withArguments:argArray
    "execute the OS command specified by the argument, aCommandPath, with
     arguments in argArray (no arguments, if nil).
     If successful, this method does NOT return and smalltalk is gone.
     If not successful, it does return. 
     Can be used on UNIX with fork or on other systems to chain to another program."

    ^ self 
        exec:aCommandPath 
        withArguments:argArray
        environment:nil
        fileDescriptors:nil
        closeDescriptors:nil 
        fork:false 
        newPgrp:false
        inDirectory:nil

    "/ never reached ...

    "Modified: / 12.11.1998 / 14:44:26 / cg"
!

exec:aCommandPath withArguments:argColl environment:env fileDescriptors:fdColl closeDescriptors:closeFdColl fork:doFork newPgrp:newPgrp 
    "Internal lowLevel entry for combined fork & exec;

     If fork is false (chain a command):
         execute the OS command specified by the argument, aCommandPath, with
         arguments in argArray (no arguments, if nil).
         If successful, this method does not return and smalltalk is gone.
         If not successful, it does return.
         Normal use is with forkForCommand.

     If fork is true (subprocess command execution):
        fork a child to do the above.
        The process id of the child process is returned; nil if the fork failed.

     fdArray contains the filedescriptors, to be used for the child (if fork is true).
        fdArray[1] = 15 -> use fd 15 as stdin.
        If an element of the array is set to nil, the corresponding filedescriptor
        will be closed for the child.
        fdArray[0] == StdIn for child
        fdArray[1] == StdOut for child
        fdArray[2] == StdErr for child
        on VMS, these must be channels as returned by createMailBox.

     closeFdArray contains descriptors that will be closed in the subprocess.
        closeDescriptors are ignored in the WIN32 & VMS versions.

     If newPgrp is true, the subprocess will be established in a new process group.
        The processgroup will be equal to id.
        newPgrp is not used on WIN32 and VMS systems.

     env specifies environment variables which are passed differently from
     the current environment. If non-nil, it must be a dictionary providing
     key-value pairs for changed/added environment variables.
     To pass a variable as empty (i.e. unset), pass a nil value.

     Notice: this used to be two separate ST-methods; however, in order to use
            vfork on some machines, it had to be merged into one, to avoid write
            accesses to ST/X memory from the vforked-child.
            The code below only does read accesses."

    ^ self
        exec:aCommandPath 
        withArguments:argColl 
        environment:env 
        fileDescriptors:fdColl 
        closeDescriptors:closeFdColl 
        fork:doFork
        newPgrp:newPgrp 
        inDirectory:nil

    "
     |id|

     id := OperatingSystem fork.
     id == 0 ifTrue:[
        'I am the child'.
        OperatingSystem exec:'/bin/ls' withArguments:#('ls' '/tmp').
        'not reached'.
     ]
    "
    "
     |id|

     id := OperatingSystem fork.
     id == 0 ifTrue:[
        'I am the child'.
        OperatingSystem
           exec:'/bin/sh'
           withArguments:#('sh' '-c' 'sleep 2;echo 1;sleep 2;echo 2').
        'not reached'.
     ].
     id printNL.
     (Delay forSeconds:3.5) wait.
     'killing ...' printNL.
     OperatingSystem sendSignal:(OperatingSystem sigTERM) to:id.
     OperatingSystem sendSignal:(OperatingSystem sigKILL) to:id
    "

    "Modified: / 20.7.1998 / 18:24:54 / cg"
    "Created: / 12.11.1998 / 14:48:25 / cg"
!

exec:aCommandPath withArguments:argArray environment:env fileDescriptors:fds closeDescriptors:closeFds fork:doFork newPgrp:newGrp inDirectory:aDirectory
    "execute an OS command"

    ^ self subclassResponsibility

    "Created: / 12.11.1998 / 14:46:15 / cg"
!

exec:aCommandPath withArguments:argArray fileDescriptors:fdArray closeDescriptors:closeFdArray fork:doFork newPgrp:newPgrp
    "combined fork & exec;
     If fork is false (chain a command):
         execute the OS command specified by the argument, aCommandPath, with
         arguments in argArray (no arguments, if nil).
         If successful, this method does not return and smalltalk is gone.
         If not successful, it does return.
         Normal use is with forkForCommand.

     If fork is true (subprocess command execution):
        fork a child to do the above.
        The process id of the child process is returned; nil if the fork failed.

     fdArray contains the filedescriptors, to be used for the child (if fork is true).
        fdArray[1] = 15 -> use fd 15 as stdin.
        If an element of the array is set to nil, the corresponding filedescriptor
        will be closed for the child.
        fdArray[0] == StdIn for child
        fdArray[1] == StdOut for child
        fdArray[2] == StdErr for child
        on VMS, these must be channels as returned by createMailBox.

     closeFdArray contains descriptors that will be closed in the subprocess.
        closeDescriptors are ignored in the WIN32 & VMS versions.

     NOTE that in WIN32 the fds are HANDLES!!

     If newPgrp is true, the subprocess will be established in a new process group.
        The processgroup will be equal to id.
        newPgrp is not used on WIN32 and VMS systems.

     Notice: this used to be two separate ST-methods; however, in order to use
            vfork on some machines, it had to be merged into one, to avoid write
            accesses to ST/X memory from the vforked-child.
            The code below only does read accesses."

    ^ self
        exec:aCommandPath 
        withArguments:argArray
        environment:nil 
        fileDescriptors:fdArray 
        closeDescriptors:closeFdArray
        fork:doFork 
        newPgrp:newPgrp
        inDirectory:nil

    "
     |id|

     id := OperatingSystem fork.
     id == 0 ifTrue:[
        'I am the child'.
        OperatingSystem exec:'/bin/ls' withArguments:#('ls' '/tmp').
        'not reached'.
     ]
    "
    "
     |id|

     id := OperatingSystem fork.
     id == 0 ifTrue:[
        'I am the child'.
        OperatingSystem
           exec:'/bin/sh'
           withArguments:#('sh' '-c' 'sleep 2;echo 1;sleep 2;echo 2').
        'not reached'.
     ].
     id printNL.
     (Delay forSeconds:3.5) wait.
     'killing ...' printNL.
     OperatingSystem sendSignal:(OperatingSystem sigTERM) to:id.
     OperatingSystem sendSignal:(OperatingSystem sigKILL) to:id
    "

    "Modified: / 12.11.1998 / 14:49:03 / cg"
    "Created: / 12.11.1998 / 14:49:07 / cg"
!

exec:aCommandPath withArguments:argArray fileDescriptors:fdArray closeDescriptors:closeFdArray fork:doFork newPgrp:newPgrp inDirectory:aDirectory
    "Internal lowLevel entry for combined fork & exec for WIN32.
     Not needed with Unix"

    ^ self
        exec:aCommandPath 
        withArguments:argArray 
        environment:nil
        fileDescriptors:fdArray
        closeDescriptors:closeFdArray 
        fork:doFork 
        newPgrp:newPgrp
        inDirectory:aDirectory

    "Modified: / 12.11.1998 / 14:47:58 / cg"
    "Created: / 12.11.1998 / 14:49:18 / cg"
!

exec:aCommandPath withArguments:argArray fork:doFork
    "execute an OS command without I/O redirection.
     The command reads its input and writes its output
     from/to whatever terminal device ST/X was started
     (typically, the xterm window)"

    ^ self 
        exec:aCommandPath 
        withArguments:argArray 
        environment:nil
        fileDescriptors:nil
        closeDescriptors:nil 
        fork:doFork 
        newPgrp:false
        inDirectory:nil

    "
     |id|

     id := OperatingSystem fork.
     id == 0 ifTrue:[
        'I am the child'.
        OperatingSystem 
            exec:'/bin/ls' 
            withArguments:#('ls' '/tmp')
            fork:false.
        'not reached'.
     ]
    "

    "
     |id|

     id := OperatingSystem fork.
     id == 0 ifTrue:[
        'I am the child'.
        OperatingSystem 
            exec:'/bin/sh' 
            withArguments:#('sh' '-c' 'sleep 2;echo 1;sleep 2;echo 2')
            fork:false.
        'not reached'.
     ].
     id printNL.
     (Delay forSeconds:3.5) wait.
     'killing ...' printNL.
     OperatingSystem sendSignal:(OperatingSystem sigTERM) to:id.
     OperatingSystem sendSignal:(OperatingSystem sigKILL) to:id
    "

    "Modified: / 15.7.1997 / 15:54:32 / stefan"
    "Modified: / 12.11.1998 / 14:44:46 / cg"
!

exec:aCommandPath withArguments:argArray fork:doFork inDirectory:aDirectory
    "execute an OS command without I/O redirection.
     The command reads its input and writes its output
     from/to whatever terminal device ST/X was started
     (typically, the xterm window)"

    ^ self 
        exec:aCommandPath
        withArguments:argArray
        environment:nil
        fileDescriptors:nil
        closeDescriptors:nil
        fork:doFork 
        newPgrp:false
        inDirectory:aDirectory

    "
     |id|

     id := OperatingSystem fork.
     id == 0 ifTrue:[
        'I am the child'.
        OperatingSystem 
            exec:'/bin/ls' 
            withArguments:#('ls' '/tmp')
            fork:false.
        'not reached'.
     ]
    "

    "
     |id|

     id := OperatingSystem fork.
     id == 0 ifTrue:[
        'I am the child'.
        OperatingSystem 
            exec:'/bin/sh' 
            withArguments:#('sh' '-c' 'sleep 2;echo 1;sleep 2;echo 2')
            fork:false.
        'not reached'.
     ].
     id printNL.
     (Delay forSeconds:3.5) wait.
     'killing ...' printNL.
     OperatingSystem sendSignal:(OperatingSystem sigTERM) to:id.
     OperatingSystem sendSignal:(OperatingSystem sigKILL) to:id
    "

    "Created: / 28.1.1998 / 14:14:03 / md"
    "Modified: / 28.1.1998 / 14:14:45 / md"
    "Modified: / 12.11.1998 / 14:45:06 / cg"
!

executableFileExtensions
    "return a collection of extensions for executable program files.
     Only req'd for msdos & vms like systems ..."

    ^ #('')

    "Created: 2.5.1997 / 11:42:29 / cg"
!

executeCommand:aCommandString
    "execute the unix command specified by the argument, aCommandString.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return true if successful, false otherwise."

     ^ self
        executeCommand:aCommandString 
        inputFrom:nil 
        outputTo:nil 
        errorTo:nil 
        inDirectory:nil
        onError:[:status| false]

    "unix:

     OperatingSystem executeCommand:'sleep 30'. 
     OperatingSystem executeCommand:'pwd'. 
     OperatingSystem executeCommand:'ls -l'. 
     OperatingSystem executeCommand:'invalidCommand'. 
     OperatingSystem executeCommand:'rm /tmp/foofoofoofoo'. 
    "

    "msdos:

     OperatingSystem executeCommand:'dir' 
     OperatingSystem executeCommand:'dir /w'
    "

    "vms:

     OperatingSystem executeCommand:'dir'
     OperatingSystem executeCommand:'purge'
     OperatingSystem executeCommand:'cc foo.c'
    "

    "Modified: / 7.1.1997 / 19:29:55 / stefan"
    "Modified: / 10.11.1998 / 20:55:37 / cg"
!

executeCommand:aCommandString inDirectory:aDirectory
    "much like #executeCommand:, but changes the current directory
     for the command. Since this is OS specific, use this instead of
     hardwiring any 'cd ..' command strings into your applictions."

     ^ self
        executeCommand:aCommandString
        inDirectory:aDirectory
        onError:[:status| false]

    "
     OperatingSystem executeCommand:'tdump date.obj' inDirectory:'c:\winstx\stx\libbasic\objbc'. 
     OperatingSystem executeCommand:'xxdir date.obj' inDirectory:'c:\winstx\stx\libbasic\objbc'. 
     OperatingSystem executeCommand:'dir' inDirectory:'c:\'. 
     OperatingSystem executeCommand:'dir' 
    "

    "Modified: / 20.1.1998 / 17:03:03 / md"
    "Modified: / 10.11.1998 / 20:28:10 / cg"
    "Created: / 10.11.1998 / 21:05:45 / cg"
!

executeCommand:aCommandString inDirectory:aDirectory onError:aBlock 
    "execute the unix command specified by the argument, aCommandString.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return true if successful.
     If not successfull, aBlock is called with an OsProcessStatus
     (containing the exit status) as argument."

    ^ self
        executeCommand:aCommandString 
        inputFrom:nil 
        outputTo:nil 
        errorTo:nil 
        inDirectory:aDirectory
        onError:aBlock

    "Modified: / 10.11.1998 / 20:54:37 / cg"
!

executeCommand:aCommandString inputFrom:anInStream outputTo:anOutStream errorTo:anErrStream inDirectory:dirOrNil lineWise:lineWise onError:aBlock
    "execute the unix command specified by the argument, aCommandString.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return true if successful.
     If not successfull, aBlock is called with an OsProcessStatus
     (containing the exit status) as argument.
     The given in, out and err streams may be arbitrary (Smalltalk-) streams;
     if any is not an external stream (which is required by the command),
     extra pipes and shuffler processes are created, which stuff the data into
     those internal stream(s).
     Nil stream args will execute the command connected to ST/X's input, output or
     error resp. - i.e. i/o will be from/to the xterminal"                                                          

    |pid exitStatus sema pIn pOut pErr externalInStream externalOutStream externalErrStream 
     inputShufflerProcess outputShufflerProcess errorShufflerProcess
     inStreamToClose outStreamToClose errStreamToClose terminateLock|

    terminateLock := Semaphore forMutualExclusion.

    (externalInStream := anInStream) notNil ifTrue:[
        "/ need an external stream for that.
        anInStream isExternalStream ifFalse:[
            pIn := ExternalStream makePipe.
            externalInStream := pIn at:1. "/ thats where the cmd reads from

            "/ start a reader process, shuffling data from the given
            "/ inStream to the pipe (which is connected to the commands input)
            inputShufflerProcess := [
                |data s|

                s := pIn at:2.            "/ thats where the shuffler writes to
                [
                    [s atEnd] whileFalse:[
                        lineWise ifTrue:[
                            data := anInStream nextLine.
                            data notNil ifTrue:[s nextPutLine:data].
                        ] ifFalse:[
                            data := anInStream nextAvailable:512.
                            data size > 0 ifTrue:[s nextPutAll:data].
                        ].
                        s flush.
                    ]
                ] valueNowOrOnUnwindDo:[
                    (pIn at:1) close.
                    (pIn at:2) close.
                ]
            ] newProcess.
            inputShufflerProcess name:'cmd input shuffler'.
            inputShufflerProcess resume.
        ]   
    ] ifFalse:[
        externalInStream := inStreamToClose := '/dev/null' asFilename readStream.
    ].

    (externalOutStream := anOutStream) notNil ifTrue:[
        "/ need an external stream for that.
        anOutStream isExternalStream ifFalse:[
            pOut := ExternalStream makePipe.
            externalOutStream := pOut at:2.   "/ thats where the cmd sends output to

            "/ start a reader process, shuffling data from the pipe
            "/ (which is connected to the commands output) to the stream 
            outputShufflerProcess := [
                |data s|

                s := pOut at:1.               "/ thats where the shuffler reads from
                [
                    [s atEnd] whileFalse:[
                        s readWait.
                        terminateLock critical:[
                            lineWise ifTrue:[
                                data := s nextLine.
                                data notNil ifTrue:[anOutStream nextPutLine:data.].
                            ] ifFalse:[
                                data := s nextAvailable:1024.
                                data size > 0 ifTrue:[anOutStream nextPutAll:data.].
                            ]
                        ]
                    ]
                ] valueNowOrOnUnwindDo:[
                    externalOutStream close.
                    [   
                        lineWise ifTrue:[
                            data := s nextLine.
                            data notNil ifTrue:[anOutStream nextPutLine:data].
                        ] ifFalse:[
                            data := s nextAvailable:1024.
                            data size > 0 ifTrue:[anOutStream nextPutAll:data].
                        ]
                    ] doUntil:[data size == 0].
                    s close.
                ].
            ] newProcess.
            outputShufflerProcess name:'cmd output shuffler'.
            outputShufflerProcess resume.
        ]   
    ] ifFalse:[
        externalOutStream := outStreamToClose := '/dev/null' asFilename readStream.
    ].

    (externalErrStream := anErrStream) notNil ifTrue:[  
        anErrStream == anOutStream ifTrue:[
            externalErrStream := externalOutStream
        ] ifFalse:[ 
            "/ need an external stream for that.
            anErrStream isExternalStream ifFalse:[
                pErr := ExternalStream makePipe.
                externalErrStream := pErr at:2.   "/ thats where the cmd sends err-output to

                "/ start a reader process, shuffling data from the pipe
                "/ (which is connected to the commands err-output) to the stream 
                errorShufflerProcess := [
                    |data s|

                    s := pErr at:1.               "/ thats where the shuffler reads from
                    [
                        [s atEnd] whileFalse:[
                            s readWait.
                            terminateLock critical:[
                                lineWise ifTrue:[
                                    data := s nextLine.
                                    data notNil ifTrue:[anOutStream nextPutLine:data.].
                                ] ifFalse:[
                                    data := s nextAvailable:1024.
                                    data size > 0 ifTrue:[anOutStream nextPutAll:data.].
                                ]
                            ]
                        ]
                    ] valueNowOrOnUnwindDo:[
                        externalErrStream close.
                        [
                            lineWise ifTrue:[
                                data := s nextLine.
                                data notNil ifTrue:[anOutStream nextPutLine:data].
                            ] ifFalse:[
                                data := s nextAvailable:1024.
                                data size > 0 ifTrue:[anOutStream nextPutAll:data].
                            ]
                        ] doUntil:[data size == 0].
                        s close.
                    ]
                ] newProcess.
                errorShufflerProcess name:'cmd err-output shuffler'.
                errorShufflerProcess resume.
            ]   
        ]   
    ] ifFalse:[
        outStreamToClose isNil ifTrue:[
            externalErrStream := errStreamToClose := '/dev/null' asFilename readStream.
        ] ifFalse:[
            externalErrStream := externalOutStream.
        ]
    ].

    sema := Semaphore new name:'OS command wait'.

    pid := Processor 
                monitor:[
                    self 
                        startProcess:aCommandString
                        inputFrom:externalInStream 
                        outputTo:externalOutStream 
                        errorTo:externalErrStream
                        inDirectory:dirOrNil.
                ] 
                action:[:status |
                    status stillAlive ifFalse:[
                        exitStatus := status.
                        sema signal.
                        self closePid:pid.
                    ].
                ].

    pid notNil ifTrue:[
        [
            sema wait.
        ] valueOnUnwindDo:[
            "/ terminate the os-command (and all of its forked commands)
            self terminateProcessGroup:pid.
            self terminateProcess:pid.
            self closePid:pid.
        ]
    ] ifFalse:[
        exitStatus := self osProcessStatusClass processCreationFailure.
    ].

    inputShufflerProcess notNil ifTrue:[
        terminateLock critical:[
            inputShufflerProcess terminate.
        ].
        inputShufflerProcess waitUntilTerminated.
    ].
    outputShufflerProcess notNil ifTrue:[
        terminateLock critical:[
            outputShufflerProcess terminate.
        ].
        outputShufflerProcess waitUntilTerminated.
    ].
    errorShufflerProcess notNil ifTrue:[
        terminateLock critical:[
            errorShufflerProcess terminate.
        ].
        errorShufflerProcess waitUntilTerminated.
    ].

    errStreamToClose notNil ifTrue:[
        errStreamToClose close
    ].
    outStreamToClose notNil ifTrue:[
        outStreamToClose close
    ].
    inStreamToClose notNil ifTrue:[
        inStreamToClose close
    ].

    exitStatus success ifFalse:[
        ^ aBlock value:exitStatus
    ].
    ^ true.

    "
     OperatingSystem
         executeCommand:'dir'
         inputFrom:nil
         outputTo:nil
         errorTo:nil
         onError:[:status | Transcript flash]

     OperatingSystem
         executeCommand:'foo'
         inputFrom:nil
         outputTo:nil
         errorTo:nil
         onError:[:status | Transcript flash]

     |s|
     s := '' writeStream.
     OperatingSystem
         executeCommand:'ls -l'
         inputFrom:nil
         outputTo:s
         errorTo:nil
         onError:[:status | Transcript flash].
     Transcript showCR:s contents.

     |s|
     s := '' writeStream.
     OperatingSystem
         executeCommand:'sh foo'
         inputFrom:nil
         outputTo:s
         errorTo:s
         onError:[:status | Transcript flash].
     Transcript showCR:s contents.
    "

    "Modified: / 25.3.1997 / 11:02:02 / stefan"
    "Modified: / 28.1.1998 / 14:46:36 / md"
    "Modified: / 10.11.1998 / 20:48:08 / cg"
    "Created: / 10.11.1998 / 20:51:11 / cg"
!

executeCommand:aCommandString inputFrom:anInStream outputTo:anOutStream errorTo:anErrStream inDirectory:dirOrNil onError:aBlock
    "execute the unix command specified by the argument, aCommandString.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return true if successful.
     If not successfull, aBlock is called with an OsProcessStatus
     (containing the exit status) as argument.
     The given in, out and err streams may be arbitrary (Smalltalk-) streams;
     if any is not an external stream (which is required by the command),
     extra pipes and shuffler processes are created, which stuff the data into
     those internal stream(s).
     Nil stream args will execute the command connected to ST/X's input, output or
     error resp. - i.e. i/o will be from/to the xterminal"                                                          

    ^ self 
        executeCommand:aCommandString inputFrom:anInStream outputTo:anOutStream errorTo:anErrStream inDirectory:dirOrNil 
        lineWise:false
        onError:aBlock

    "
     OperatingSystem
         executeCommand:'dir'
         inputFrom:nil
         outputTo:nil
         errorTo:nil
         onError:[:status | Transcript flash]

     OperatingSystem
         executeCommand:'foo'
         inputFrom:nil
         outputTo:nil
         errorTo:nil
         onError:[:status | Transcript flash]

     |s|
     s := '' writeStream.
     OperatingSystem
         executeCommand:'ls -l'
         inputFrom:nil
         outputTo:s
         errorTo:nil
         onError:[:status | Transcript flash].
     Transcript showCR:s contents.

     |s|
     s := '' writeStream.
     OperatingSystem
         executeCommand:'sh foo'
         inputFrom:nil
         outputTo:s
         errorTo:s
         onError:[:status | Transcript flash].
     Transcript showCR:s contents.
    "

    "Modified: / 25.3.1997 / 11:02:02 / stefan"
    "Modified: / 28.1.1998 / 14:46:36 / md"
    "Modified: / 10.11.1998 / 20:48:08 / cg"
    "Created: / 10.11.1998 / 20:51:11 / cg"
!

executeCommand:aCommandString inputFrom:anExternalInStream outputTo:anExternalOutStream errorTo:anExternalErrStream onError:aBlock
    "execute the unix command specified by the argument, aCommandString.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return true if successful.
     If not successfull, aBlock is called with an OsProcessStatus
     (containing the exit status) as argument."

    ^ self
        executeCommand:aCommandString 
        inputFrom:anExternalInStream 
        outputTo:anExternalOutStream 
        errorTo:anExternalErrStream 
        inDirectory:nil
        onError:aBlock

    "
        OperatingSystem
            executeCommand:'dir'
            inputFrom:nil
            outputTo:nil
            errorTo:nil
            onError:[:status | Transcript flash]
        
        OperatingSystem
            executeCommand:'foo'
            inputFrom:nil
            outputTo:nil
            errorTo:nil
            onError:[:status | Transcript flash]
    "

    "Modified: / 10.11.1998 / 20:51:39 / cg"
!

executeCommand:aCommandString onError:aBlock
    "execute the unix command specified by the argument, aCommandString.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return true if successful.
     If not successfull, aBlock is called with an OsProcessStatus
     (containing the exit status) as argument."

    ^ self
        executeCommand:aCommandString 
        inputFrom:nil 
        outputTo:nil 
        errorTo:nil 
        inDirectory:nil
        onError:aBlock

    "unix:

     OperatingSystem executeCommand:'sleep 30' onError:[]. 
     OperatingSystem executeCommand:'pwd' onError:[:status|status inspect]. 
     OperatingSystem executeCommand:'ls -l' onError:[]. 
     OperatingSystem executeCommand:'invalidCommand' onError:[:status| status inspect]. 
     OperatingSystem executeCommand:'rm /tmp/foofoofoofoo'onError:[:status | status inspect]. 

     OperatingSystem executeCommand:'dir' onError:[]. 
     OperatingSystem executeCommand:'foo' onError:[]. 
        
    "

    "Modified: / 25.3.1997 / 11:06:43 / stefan"
    "Modified: / 28.1.1998 / 14:46:56 / md"
    "Created: / 5.6.1998 / 19:02:09 / cg"
    "Modified: / 10.11.1998 / 20:55:02 / cg"
!

executeCommand:aCommandString onError:aBlock inDirectory:aDirectory
    "execute the unix command specified by the argument, aCommandString.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return true if successful.
     If not successfull, aBlock is called with an OsProcessStatus
     (containing the exit status) as argument."

    <resource:#obsolete>

    self obsoleteMethodWarning:'use executeCommand:inDirectory:onError:'.

    ^ self
        executeCommand:aCommandString 
        inputFrom:nil 
        outputTo:nil 
        errorTo:nil 
        inDirectory:aDirectory
        onError:aBlock

    "Modified: / 10.11.1998 / 20:54:37 / cg"
!

executeCommand:aCommandString outputTo:outStreamOrNil errorTo:errStreamOrNil inDirectory:aDirectory
    "much like #executeCommand:, but changes the current directory
     for the command. Since this is OS specific, use this instead of
     hardwiring any 'cd ..' command strings into your applictions."

     ^ self
        executeCommand:aCommandString
        inputFrom:nil
        outputTo:outStreamOrNil
        errorTo:errStreamOrNil
        inDirectory:aDirectory
        onError:[:status| false]

    "
     OperatingSystem executeCommand:'tdump date.obj' inDirectory:'c:\winstx\stx\libbasic\objbc'. 
     OperatingSystem executeCommand:'xxdir date.obj' inDirectory:'c:\winstx\stx\libbasic\objbc'. 
     OperatingSystem executeCommand:'dir' inDirectory:'c:\'. 
     OperatingSystem executeCommand:'dir' 
    "

    "Modified: / 20.1.1998 / 17:03:03 / md"
    "Modified: / 10.11.1998 / 20:28:10 / cg"
    "Created: / 10.11.1998 / 21:05:45 / cg"
!

fork
    "fork a new (HEAVY-weight) unix process.
     Not supported with MSDOS & VMS systems.
     Dont confuse this with Block>>fork, which creates
     lightweight smalltalk processes. This method will return
     0 to the child process, and a non-zero number (which is the childs
     unix-process-id) to the parent (original) process.

     In normal situations, you dont need to use this low level entry; see
     #startProcess: and #executCommand: for higher level interfaces."

    "/
    "/ not supported by OS
    "/

    ^ UnsupportedOperationSignal raise
!

getCommandOutputFrom:aCommand
    "execute a simple command (such as hostname) and
     return the commands first line of output as a string (forget stdErr).
     If the command generates multiple output lines, only the first line is returned.
     If the commands does not generate any output, an empty string is returned;
     if the command fails, nil is returned."

    |result|

    result := self getCommandOutputFrom:aCommand maxNumberOfLines:1 errorDisposition:#discard.
    result notNil ifTrue:[
        ^ result firstIfEmpty:['']
    ].
    ^ result

    "
     OperatingSystem getCommandOutputFrom:'hostname' 
     OperatingSystem getCommandOutputFrom:'pwd'   
     OperatingSystem getCommandOutputFrom:'sleep 1'   
     OperatingSystem getCommandOutputFrom:'foo'   
    "

!

getCommandOutputFrom:aCommand maxNumberOfLines:numLinesOrNil errorDisposition:errorDisposition
    "execute a simple command (such as hostname) and
     return the commands output as a collection of strings,
     but only up to the given number of lines (if non-nil).
     If the command generates more output, only the first nLines are returned
     (but the command is allowed to finish execution).
     If the commands does not generate any output, an empty string is returned;
     if the command fails, nil is returned.
     errorDisposition controls where the stdErr output should go,
     and may be one of #discard, #inline or #stderr (default).
     #discard causes stderr to be discarded (/dev/null), 
     #inline causes it to be written to smalltalks own stdout and
     #stderr causes it to be written to smalltalks own stderr.
     Nil is treated like #stderr"

    |result|

    PipeFailed ~~ true ifTrue:[
        PipeStream openErrorSignal handle:[:ex |
            PipeFailed := true.
            'OperatingSystem [warning]: cannot fork/popen' errorPrintCR.
            ex return.
        ] do:[
            |p line|

            p := PipeStream 
                    readingFrom:aCommand
                    errorDisposition:errorDisposition
                    inDirectory:nil.
            p notNil ifTrue:[
                result := StringCollection new.
                [p atEnd] whileFalse:[
                    line := p nextLine.
                    (numLinesOrNil isNil 
                    or:[result size < numLinesOrNil]) ifTrue:[
                        result add:line
                    ].
                ].
                p close.
                p exitStatus success ifFalse:[
                    result isEmpty ifTrue:[
                        result := nil
                    ]
                ].
            ].
        ].
    ].
    ^ result

    "
     OperatingSystem getCommandOutputFrom:'ls' maxNumberOfLines:1
     OperatingSystem getCommandOutputFrom:'ls' maxNumberOfLines:10
     OperatingSystem getCommandOutputFrom:'ls' maxNumberOfLines:nil
     OperatingSystem getCommandOutputFrom:'foo' maxNumberOfLines:nil
    "

    "Modified: / 19.5.1999 / 14:25:02 / cg"
!

getFullCommandOutputFrom:aCommand
    "execute a command and
     return the commands output as a collection of strings (ignoring stdErr).
     If the commands does not generate any output, an empty string is returned;
     if the command fails, nil is returned."

    ^ self getCommandOutputFrom:aCommand maxNumberOfLines:nil errorDisposition:#discard

    "
     OperatingSystem getFullCommandOutputFrom:'mt status'
    "

!

getVMSSymbol:aSymbolString
    "get a symbols value, or nil if there is none"

    ^ nil

    "Created: / 5.6.1998 / 19:02:50 / cg"
    "Modified: / 5.6.1998 / 19:03:15 / cg"
!

nameOfSTXExecutable
    "return the name of the running ST/X executable program.
     Usually, 'stx' is returned - but may be different for
     standAlone apps."

%{
    extern char *__stxExecutableName__();

    RETURN (__MKSTRING(__stxExecutableName__()));
%}
    "
     OperatingSystem nameOfSTXExecutable
    "
!

pathOfCommand:aCommand
    "find where aCommand's executable file is;
     return its full pathName if there is such a command, otherwise
     return nil."

    ^ self subclassResponsibility
!

pathOfSTXExecutable
    "return the full path of the running ST/X executable program.
     Usually, '/../../stx' is returned - but may be different for
     standAlone apps."

    ^ self pathOfCommand:(self nameOfSTXExecutable)

    "
     OperatingSystem pathOfSTXExecutable
    "
!

primExec:aCommandPath withArguments:argArray fileDescriptors:fdArray closeDescriptors:closeFdArray fork:doFork newPgrp:newPgrp inPath:dirName
    "Internal lowLevel entry for combined fork & exec"

    self subclassResponsibility
!

startProcess:aCommandString
    "start executing the OS command as specified by the argument, aCommandString
     as a separate process; do not wait for the command to finish.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return the processId if successful, nil otherwise.
     Use #waitForProcess: for synchronization and exec status return,
     or #killProcess: to stop it."

    ^ self
        startProcess:aCommandString 
        inputFrom:nil 
        outputTo:nil 
        errorTo:nil 
        inDirectory:nil

    "
     |pid|

     pid := OperatingSystem startProcess:'sleep 2; echo 1; sleep 2; echo 2'.
     (Delay forSeconds:3) wait.
     OperatingSystem killProcess:pid.
    "
    "
     |pid|

     pid := OperatingSystem startProcess:'dir/l'.
     (Delay forSeconds:1) wait.
     OperatingSystem killProcess:pid.
    "
    "
     |pid|

     pid := OperatingSystem 
                startProcess:'dir/l'
                inputFrom:nil
                outputTo:Stdout
                errorTo:nil
                inDirectory:nil.
     (Delay forSeconds:2) wait.
     OperatingSystem killProcess:pid.
    "

    "Modified: / 21.3.1997 / 10:04:35 / dq"
    "Modified: / 10.11.1998 / 21:03:50 / cg"
!

startProcess:aCommandString inDirectory:aDirectory
    "start executing the OS command as specified by the argument, aCommandString
     as a separate process; do not wait for the command to finish.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual.
     Return the processId if successful, nil otherwise.
     Use #waitForProcess: for synchronization and exec status return,
     or #killProcess: to stop it."

    ^ self
        startProcess:aCommandString 
        inputFrom:nil 
        outputTo:nil 
        errorTo:nil 
        inDirectory:aDirectory
    "
     |pid|

     pid := OperatingSystem startProcess:'sleep 2; echo 1; sleep 2; echo 2'.
     (Delay forSeconds:3) wait.
     OperatingSystem killProcess:pid.
    "

    "Modified: / 21.3.1997 / 10:04:35 / dq"
    "Modified: / 28.1.1998 / 14:13:33 / md"
    "Modified: / 10.11.1998 / 20:59:33 / cg"
!

startProcess:aCommandString inputFrom:anExternalInStream outputTo:anExternalOutStream errorTo:anExternalErrStream
    "start executing the OS command as specified by the argument, aCommandString
     as a separate process; do not wait for the command to finish.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual ('cmd.com' in your MSDOS manual).
     The command gets stdIn, stdOut and stdErr assigned from the arguments;
     each may be nil.
     Return the processId if successful, nil otherwise.
     Use #monitorPid:action: for synchronization and exec status return,
     or #killProcess: to stop it."

     ^ self     
        startProcess:aCommandString 
        inputFrom:anExternalInStream 
        outputTo:anExternalOutStream 
        errorTo:anExternalErrStream 
        inDirectory:nil

    "Modified: / 10.11.1998 / 20:59:05 / cg"
!

startProcess:aCommandString inputFrom:anExternalInStream outputTo:anExternalOutStream errorTo:anExternalErrStream inDirectory:dir
    "start executing the OS command as specified by the argument, aCommandString
     as a separate process; do not wait for the command to finish.
     The commandString is passed to a shell for execution - see the description of
     'sh -c' in your UNIX manual ('cmd.com' in your MSDOS manual).
     The command gets stdIn, stdOut and stdErr assigned from the arguments;
     each may be nil.
     Return the processId if successful, nil otherwise.
     Use #monitorPid:action: for synchronization and exec status return,
     or #killProcess: to stop it."

     self subclassResponsibility

    "Created: / 10.11.1998 / 20:58:00 / cg"
! !

!AbstractOperatingSystem class methodsFor:'file access'!

closeFd:anInteger
    "low level close of a filedescriptor"

    self subclassResponsibility
!

createDirectory:aPathName
    "create a new directory with name 'aPathName', which may be an absolute
     path, or relative to the current directory.
     Return true if successful (or the directory existed already), false if failed.
     This is a low-level entry - use Filename protocol for compatibility."

    "/ if it already exists this is ok

    self subclassResponsibility
!

createHardLinkFrom:oldPath to:newPath
    "link the file 'oldPath' to 'newPath'. The link will be a hard link.
     Return true if successful, false if not."

    "/
    "/ assume that this OperatingSystem does not support links
    "/
    ^ UnsupportedOperationSignal raise

    "Created: / 13.8.1998 / 21:37:12 / cg"
    "Modified: / 13.8.1998 / 21:38:39 / cg"
!

createSymbolicLinkFrom:oldPath to:newPath
    "make a link from the file 'oldPath' to the file 'newPath'.
     The link will be a soft (symbolic) link.
     Return true if successful, false if not."

    "/
    "/ assume that this OperatingSystem does not support symbolic links
    "/
    ^ UnsupportedOperationSignal raise

    "Created: / 13.8.1998 / 21:38:24 / cg"
    "Modified: / 13.8.1998 / 21:38:43 / cg"
!

linkFile:oldPath to:newPath
    "link the file 'oldPath' to 'newPath'. The link will be a hard link.
     Return true if successful, false if not.
     This method has been renamed - it remains in existance for
     backward compatibility."

    ^ self createHardLinkFrom:oldPath to:newPath

    "
     OperatingSystem linkFile:'foo' to:'bar'
    "

    "Modified: / 13.8.1998 / 21:37:24 / cg"
!

recursiveCopyDirectory:fullPathName to:destinationPathName
    "copy the directory named 'fullPathName' and all contained 
     files/directories recursively to destinationPathName.
     Return true if successful.
     Here, false is returned and the caller should be prepared
     for a fallBack solution.
     Notice: 
        this is not a public interface; instead, it is used
        internally by the Filename class, to try a fast copy
        before doing things manually.
        Please use Filename recursiveCopyTo:"

    ^ false

    "
     OperatingSystem recursiveCopyDirectory:'.' to:'/tmp/foo'
     OperatingSystem recursiveRemoveDirectory:'/tmp/foo'
    "

    "Modified: / 5.5.1999 / 13:29:16 / cg"
!

recursiveCreateDirectory:dirName
    "create a directory - with all parent dirs if needed.
     Return true if successful, false otherwise. If false
     is returned, a partial created tree may be left,
     which is not cleaned-up here."

    self createDirectory:dirName.
    (self isDirectory:dirName) ifFalse:[
        (self recursiveCreateDirectory:(dirName asFilename directoryName)) ifFalse:[^ false].
        ^ self createDirectory:dirName
    ].
    ^ true

    "
     OperatingSystem recursiveCreateDirectory:'foo/bar/baz'
     OperatingSystem recursiveRemoveDirectory:'foo'
    "

    "Modified: 7.3.1996 / 15:26:22 / cg"
!

recursiveRemoveDirectory:fullPathName
    "remove the directory named 'fullPathName' and all contained files/directories.
     Return true if successful.
     Here, false is returned and the caller should be prepared
     for a fallBack solution.
     Notice: 
        this is not a public interface; instead, it is used
        internally by the Filename class, to try a fast remove
        before doing things manually.
        Please use Filename recursiveRemoveDirectory:"

    ^ false

    "
     OperatingSystem recursiveCreateDirectory:'foo/bar/baz'
     OperatingSystem recursiveRemoveDirectory:'foo'
    "

    "Modified: / 5.5.1999 / 13:30:11 / cg"
!

removeDirectory:fullPathName
    "remove the directory named 'fullPathName'. 
     The directory must be empty and you must have appropriate access rights.
     Return true if successful, false if directory is not empty or no permission.
     This is a lowLevel entry - use Filename protocol for compatibility."

    self subclassResponsibility
!

removeFile:fullPathName
    "remove the file named 'fullPathName'; return true if successful.
     This is a lowLevel entry - use Filename protocol for compatibility."

    self subclassResponsibility
!

renameFile:oldPath to:newPath
    "rename the file 'oldPath' to 'newPath'. 
     Someone else has to care for the names to be correct and 
     correct for the OS used - therefore, this should not be called
     directlt. Instead, use Filename protocol to rename; this cares for
     any invalid names.
     Returns true if successful, false if not"

    self subclassResponsibility
!

truncateFile:aPathName to:newSize
    "change a files size return true on success, false on failure.
     This may not be supported on all architectures.

     This is a low-level entry - use Filename protocol."

    self subclassResponsibility
! !

!AbstractOperatingSystem class methodsFor:'file access rights'!

accessMaskFor:aSymbol
    "return the access bits mask for numbers as returned by 
     OperatingSystem>>accessModeOf:
     and expected by OperatingSystem>>changeAccessModeOf:to:.
     Since these numbers are OS dependent, always use the mask
     (never hardcode 8rxxx into your code)."

    self subclassResponsibility
!

accessModeOf:aPathName
    "return a number representing access rights rwxrwxrwx for owner,
     group and others. Return nil if such a file does not exist.
     Notice that the returned number is OS dependent - use the 
     modeMasks as returned by OperatingSystem>>accessMaskFor:"

    "
     this could have been implemented as:
        (self infoOf:aPathName) at:#mode
     but for huge directory searches the code below is faster
    "

    ^ (self infoOf:aPathName) at:#mode

   "
    (OperatingSystem accessModeOf:'/') printStringRadix:8
   "
!

changeAccessModeOf:aPathName to:modeBits
    "change the access rights of aPathName to the OS dependent modeBits.
     You should construct this mask using accessMaskFor, to be OS
     independent. Return true if changed, 
     false if such a file does not exist or change was not allowd."

    self subclassResponsibility
! !

!AbstractOperatingSystem class methodsFor:'file locking'!

lockFD:aFileDescriptor shared:isSharedReadLock blocking:blockIfLocked
   "set a lock on the file represented by aFileDescriptor.
    (such as returned by ExternalStream>>fileDescriptor).
    On some systems, only advisory locks are available -
    these depends on other accessors to also perform the locking operation.
    If they do not, they may still access the file 
    (on some systems, locks are mandatory, on others, they are advisory). 
    The isSharedReadLock argument (if true) specifies if multiple readers
    are to be allowed - if false, they are not.
    On some systems, all locks are non-exclusive locks.

    Returns true, if the lock was aquired, false otherwise.

    Notice, that not all OS's support these locks; 
    on some, this may simply be a no-op.
    Also notice, that some systems block the process, to wait for the lock.
    This can (again: on some systems) be avoided by passing a false blockIfLocked
    argument."

    ^ false
!

supportsFileLinks
    "return true, if the OS supports file links (hard links).
     Typically, only unix returns true here."

    ^ false
!

supportsFileLocks
    "return true, if the OS supports file locking"

    ^ false

    "
     OperatingSystem supportsFileLocks
    "
!

supportsNonBlockingFileLocks
    "return true, if the OS supports nonBlocking file locking
     (i.e. with immediate return instead of waiting for the lock)"

    ^ false

    "
     OperatingSystem supportsNonBlockingFileLocks
    "
!

supportsSharedLocks
    "return true, if the OS supports shared (i.e. multiple reader)
     file locking. Assume false here - redefined in concrete classes."

    ^ false

    "
     OperatingSystem supportsNonBlockingFileLocks
    "

    "Modified: / 5.5.1999 / 01:08:03 / cg"
!

supportsSymbolicLinks
    "return true, if the OS supports symbolic links on files/directories.
     Typically, only Unix returns true here"

    ^ false
!

unlockFD:aFileDescriptor
    "clear a file lock on the file represented by aFileDescriptor,
     which was previously aquired by #lockFD:.
     Return false, if the unlock failed 
     (which may happens when a wrong fd is passed, 
      no lock was set previously, or the systsem does not support locks).
     Notice, that not all OS's support file locks; 
     on some, this may simply be a no-op."
     
    ^ false

    "Modified: / 10.9.1998 / 17:54:15 / cg"
! !

!AbstractOperatingSystem class methodsFor:'file queries'!

baseNameOf:aPath
    <resource:#obsolete>

    self obsoleteMethodWarning:'use asFilename baseName'.
    ^ aPath asFilename baseName
!

caseSensitiveFilenames
    "return true, if the OS has caseSensitive file naming.
     On MSDOS, this will return false; 
     on a real OS, we return true."

    self subclassResponsibility
!

compressPath:pathName
    "return the pathName compressed - that is, remove all ..-entries
     and . entries. This does not always (in case of symbolic links)
     return the true pathName and is therefore used as a fallback
     if realPath and popen failed."

    self subclassResponsibility
!

directoryNameOf:aPath
    <resource:#obsolete>

    self obsoleteMethodWarning:'use asFilename directoryName'.
    ^ aPath asFilename directoryName
!

fileSeparator
    "return the character used to separate names in a path.
     This character differs for MSDOS and other systems,
     (but those are currently not supported - so this is some
      preparation for the future)"

    ^ $/   "/ must be redefined for systems, where this is not true (i.e. MSDOS)
!

getDiskInfoOf:aDirectoryPath
    "return some disk info. 
     The amount of information returned depends upon the OS, and is
     not guaranteed to be consistent across architectures.
     On unix and msdos, the information returned is (at least):
        freeBytes
        totalBytes
     Do not depend on any information being present in the returned dictionary;
     users of this method should always use #at:ifAbsent:, and care for the absent case.
     Nil is returned if no such information can be obtained.
    "

    ^ nil

    "
     OperatingSystem getDiskInfoOf:'/'
     OperatingSystem getDiskInfoOf:'.'
    "

    "Modified: / 22.5.1999 / 00:36:06 / cg"
!

getDriveList
    "return a list of volumes in the system. 
     On unix, no such thing like a volume exists 
     - there, a syntetic list with root, home & current is returned. 
     On MSDOS, a list of drive letters is (eventually) returned.
     On VMS, a list of volumes is (eventually) returned."

    "/
    "/ default: return an array filled with
    "/ root, home and current directories.
    "/
    ^ Array 
        with:'/'
        with:(self getHomeDirectory)
        with:(Filename currentDirectory pathName)

    "Modified: / 5.5.1999 / 01:06:26 / cg"
!

getMountedVolumes
    "return info about mounted volumes. 
     The amount of information returned depends upon the OS, and is
     not guaranteed to be consistent across architectures.
     On unix, the information returned is (at least):
        mountPoint - mount point
        fileSystem - device or NFS-remotePath
    "

    ^ #()

    "
     OperatingSystem getMountedVolumes
    "

    "Modified: / 22.5.1999 / 00:36:06 / cg"
!

getNullDevice
    "get the name of the null-device. Nil is returned if not supported"

    ^ nil

    "Created: / 19.5.1999 / 12:24:59 / cg"
!

idOf:aPathName
    "return the fileNumber (i.e. inode number) of a file.

     Not all operatingSystems may provide this - on those that do not,
     some dummy id will be returned.
     On unix, this information can be used to check for two files being 
     physically identical, even if found in different directories 
     (i.e. if they are hardLinked)."

    |i id|

    id := self primIdOf:aPathName.
    id notNil ifTrue:[^ id].

    i := self infoOf:aPathName.
    i notNil ifTrue:[^ i id].
    ^ nil.

    "
     OperatingSystem idOf:'/'
    "
!

infoOf:aPathName
    "return some object filled with info for the file 'aPathName';
     the info (for which corresponding access methods are understood by
     the returned object) is:
         type            - a symbol giving the files type
         mode            - numeric access mode 
         uid             - owners user id
         gid             - owners group id
         size            - files size
         id              - files number (i.e. inode number)
         accessed        - last access time (as Timestamp)
         modified        - last modification time (as Timestamp)
         statusChanged   - last status change time (as Timestamp)
         alternativeName - (windows only: the MSDOS name of the file)

     Some of the fields may be returned as nil on systems which do not provide
     all of the information.
     Return nil if such a file does not exist. 
     For symbolic links (if supported by the OS), 
     the info of the pointed-to-file (i.e. the target) is returned;
     use #linkInfoOf: to get info about the link itself.
    "

    self subclassResponsibility
!

isDirectory:aPathName
    "return true, if 'aPathName' is a valid directory path name.
     (i.e. exists and is a directory).
     This also returns true for symbolic links pointing to a directory;
     if you need to check for this, use #linkInfo:."

    ^ (self infoOf:aPathName) type == #directory
!

isExecutable:aPathName
    "return true, if the given file is executable.
     For symbolic links, the pointed-to-file is checked."

    self subclassResponsibility
!

isReadable:aPathName
    "return true, if the file/dir 'aPathName' is readable.
     For symbolic links, the pointed-to-file is checked."

    self subclassResponsibility
!

isSymbolicLink:aPathName
    "return true, if the given file is a symbolic link"

    ^ (self linkInfoOf:aPathName) notNil

    "
     OperatingSystem isSymbolicLink:'Make.proto'
     OperatingSystem isSymbolicLink:'Makefile' 
    "
!

isValidPath:aPathName
    "return true, if 'aPathName' is a valid path name
     (i.e. the file or directory exists)"

    self subclassResponsibility
!

isWritable:aPathName
    "return true, if the given file is writable.
     For symbolic links, the pointed-to-file is checked."

    self subclassResponsibility
!

linkInfoOf:aPathName
    "return a dictionary filled with info for the file 'aPathName',
     IFF aPathName is a symbolic link. 
     If aPathName is invalid, or its NOT a symbolic link, nil is returned.
     (which means, that systems like VMS or MSDOS always return nil here.)

     The contents of the dictionary gives info about the link itself,
     on contrast to #infoOf:, which returns the info of the pointed to file
     in case of a symbolic link."
     
    self subclassResponsibility
!

mimeTypeForFilename:aFilename
    "given a filename, return a corresponding mimeType.
     This is placed here, to allow for OS-specific configuration
     files and/or the win32 registry to be consultet.
     Returns nil if no mimeType for the given name is known."

    ^ nil
!

mimeTypeForSuffix:aFileSuffix
    "given a file suffix, return a corresponding mimeType.
     This is placed here, to allow for OS-specific configuration
     files and/or the win32 registry to be consultet.
     Returns nil if no mimeType for the given suffix is known."

    ^ nil
!

parentDirectoryName
    "return the name used to refer to parent directories.
     In MSDOS, Unix and other systems this is '..', but maybe different
     for other systems.
     (but those are currently not supported - so this is some
      preparation for the future)"

    ^ '..'
!

pathNameOf:pathName
    "return the pathName of the argument, aPathString,
     - thats the full pathname of the directory, starting at '/'.
     This method needs the path to be valid
     (i.e. all directories must exist, be readable and executable).
     Notice: if symbolic links are involved, the result may look different
     from what you expect."

    self subclassResponsibility
!

primIdOf:aPathName
    "the actual code to return the fileNumber (i.e. inode number) of a file."

    self subclassResponsibility
!

primPathNameOf:pathName
    "return the pathName of the argument, aPathString,
     - thats the full pathname of the directory, starting at '/'.
     This method here returns nil, if the OS does not provide a
     realPath library function.
     Notice: if symbolic links are involved, the result may look different
     from what you expect."

    self subclassResponsibility
!

timeOfLastAccess:aPathName
    "return the time, when the file was last accessed.
     For nonexistent files, nil is returned."

    ^ (self infoOf:aPathName) accessed 
!

timeOfLastChange:aPathName
    "return the time, when the file was last changed. 
     For nonexistent files, nil is returned."

    ^ (self infoOf:aPathName) modified
!

typeOf:aPathName
    "return the type of a file as a symbol; for nonexistent files,
     nil is returned.
     Notice: for symbolic links, the type of the pointed-to file is returned."

    ^ (self infoOf:aPathName) type 
!

volumeNameOf:aPathString
    "return the volumeName of the argument, aPath
     - thats the name of the volume where aPath is.
     Not all OperatingSystems support/use volumes; on unix,
     this always returns an empty string."

    ^ ''
! !

!AbstractOperatingSystem class methodsFor:'interprocess communication'!

createCOMFileForVMSCommand:aCommandString in:aDirectory
    "this is only implemented/required for VMS systems, to execute commands"

    ^ UnsupportedOperationSignal raise

    "Created: / 19.5.1999 / 12:16:31 / cg"
    "Modified: / 19.5.1999 / 14:22:05 / cg"
!

createMailBox
    "this is only implemented/required for VMS systems, to emulate pipes"

    ^ UnsupportedOperationSignal raise

    "Created: / 19.5.1999 / 12:14:56 / cg"
    "Modified: / 19.5.1999 / 14:22:22 / cg"
!

destroyMailBox:mbx
    "this is only implemented/required for VMS systems, to emulate pipes"

    ^ UnsupportedOperationSignal raise

    "Created: / 19.5.1999 / 12:16:43 / cg"
    "Modified: / 19.5.1999 / 14:22:33 / cg"
!

mailBoxNameOf:mbx
    "this is only implemented/required for VMS systems, to emulate pipes"

    ^ UnsupportedOperationSignal raise

    "Created: / 19.5.1999 / 12:14:56 / cg"
    "Modified: / 19.5.1999 / 14:22:40 / cg"
!

makePipe
    "this is only implemented/required for non-VMS systems"

    ^ UnsupportedOperationSignal raise

    "Modified: / 19.5.1999 / 14:23:09 / cg"
! !

!AbstractOperatingSystem class methodsFor:'interrupts & signals'!

blockInterrupts
    "disable interrupt processing - if disabled, incoming
     interrupts will be registered and handled as soon as
     interrupts are reenabled by OperatingSystemclass>>unblockInterrupts.
     Returns the previous blocking status i.e. true if interrupts
     where already blocked. You need this information for proper
     unblocking, in case of nested block/unblock calls."

%{  /* NOCONTEXT */
    RETURN ( __BLOCKINTERRUPTS() );
%}
!

defaultSignal:signalNumber
    "revert to the default action on arrival of a (Unix-)signal.
     Dont confuse Unix signals with smalltalk signals.
     WARNING: for some signals, it is no good idea to revert to default;
     for example, the default for SIGINT (i.e. ^C) is to exit; while the
     default for SIGQUIT (^ \) is to dump core.
     Also, NOTICE that signal numbers are not portable between unix
     systems - use OperatingSystem sigXXX to get the numeric value for
     a signal."

    self subclassResponsibility
!

disableChildSignalInterrupts
    "disable childSignal interrupts 
     (SIGCHLD, if the architecture supports it).
     We have to set the signal back to default, because ignoring 
     SIGCHLD breaks wait & co"

    ^ self defaultSignal:(self sigCHLD)

    "Created: 5.1.1996 / 15:45:28 / stefan"
!

disableIOInterruptsOn:fd
    "turn off IO interrupts for a filedescriptor"

    self subclassResponsibility
!

disableSignal:signalNumber
    "disable (Unix-) signal processing for signalNumber.
     Dont confuse Unix signals with smalltalk signals.
     WARNING: for some signals, it is no good idea to disable
     them; for example, disabling the SIGINT signal turns off ^C
     handling.
     Also, NOTICE that signal numbers are not portable between unix
     systems - use OperatingSystem sigXXX to get the numeric value for
     a signal.
     Use only for fully debugged stand alone applications."

    self subclassResponsibility
!

disableTimer
    "disable timer interrupts.
     WARNING: 
        the system will not operate correctly with timer interrupts
        disabled, because no scheduling or timeouts are possible."

    self subclassResponsibility
!

disableUserInterrupts
    "disable userInterrupt processing;
     when disabled, no ^C processing takes place.
     WARNING:
         If at all, use this only for debugged stand-alone applications, since
         no exit to the debugger is possible with user interrupts disabled.
         We recommend setting up a handler for the signal instead of disabling it."

    self disableSignal:(self sigBREAK).
    self disableSignal:(self sigINT).
!

enableAbortInterrupts
    "enable abort signalhandling, and make it a regular signalInterrupt.
     (the default will dump core and exit - which is not a good idea for
      end-user applications ...).
     This is especially useful, if linked-in C-libraries call abort() ..."

    self enableSignal:(self sigABRT)
!

enableChildSignalInterrupts
    "enable childSignal interrupts 
     (SIGCHLD, if the architecture supports it).
     After enabling, these signals will send the message 
     'childSignalInterrupt' to the ChildSignalInterruptHandler object."

    self enableSignal:(self sigCHLD)
!

enableFpExceptionInterrupts
    "enable floating point exception interrupts (if the
     architecture supports it).
     After enabling, fpu-exceptions will send the message 
     'fpuExceptionInterrupt' to the FPUExceptionInterruptHandler object."

    self enableSignal:(self sigFP)
!

enableHardSignalInterrupts
    "enable hard signal exception interrupts (trap, buserror & segm. violation).
     After enabling, these exceptions will send the message 
     'signalInterrupt' to the SignalInterruptHandler object."

    "/ leads to trouble ...
"/    self enableSignal:(self sigPIPE).

    "/ ... better to ignore them, and let it be handled as a writeErrorSignal.
    self disableSignal:(self sigPIPE).

    self enableSignal:(self sigILL).
    self enableSignal:(self sigBUS).
    self enableSignal:(self sigSEGV).
    self enableSignal:(self sigFP).
    self enableSignal:(self sigEMT).
!

enableIOInterruptsOn:fd
    "turn on IO interrupts for a filedescriptor"

    self subclassResonsibility
!

enablePowerSignalInterrupt
    "enable powerFail signal exception interrupts (sigPWR).
     After enabling, this signal will trigger the writing of a crash-image"

    self enableSignal:(self sigPWR).
!

enableQuitInterrupts
    "enable quitInterrupt (usually ^\) handling, and make it a userInterrupt.
     (the default will dump core and exit - which is not a good idea for
      end-user applications ...)"

    self enableSignal:(self sigQUIT)
!

enableSignal:signalNumber
    "enable (Unix-)signal processing for signalNumber.
     Dont confuse Unix signals with smalltalk signals.
     The signal will be delivered to one of the standard handlers
     (SIGINT, SIGQUIT, etc) or to a general handler, which
     sends #signalInterrupt:.

     NOTICE that signal numbers are not portable between unix
     systems - use OperatingSystem sigXXX to get the numeric value for
     a signal."

    self subclassResonsibility
!

enableTimer:milliSeconds
    "setup for a timerInterrupt, to be signalled after some (real) time."

    self subclassResonsibility
!

enableUserInterrupts
    "enable userInterrupt (^C) handling;
     when enabled, ^C in the terminal window will send the message
     'userInterrupt' to the UserInterruptHandler object."

    self enableSignal:(self sigINT).
    self enableSignal:(self sigBREAK).
!

interruptPending
    "return true, if an interrupt is pending. The returned value is
     invalid if interrupts are not currently blocked, since otherwise 
     the interrupt is usually already handled before arriving here,
     or may be served while returning from here."

%{  /* NOCONTEXT */
    extern OBJ __INTERRUPTPENDING();

    RETURN ( __INTERRUPTPENDING() );
%}        
!

interruptsBlocked
    "return true, if interrupt handling is currently disabled;
     false otherwise."

%{  /* NOCONTEXT */
    extern OBJ __INTERRUPTS_BLOCKED();

    RETURN ( __INTERRUPTS_BLOCKED() );
%}
!

killProcess:processId
    "kill an OS process.
     The process has a no chance to do some cleanup.

     WARNING: in order to avoid zombie processes (on unix),
              you may have to fetch the processes exitstatus with
              OperatingSystem>>getStatusOfProcess:aProcessId."

    self subclassResponsibility

    "Modified: / 10.6.1998 / 12:00:07 / cg"
!

killProcessGroup:processGroupId
    "kill an OS process group.
     The process has NO chance to do some cleanup.

     WARNING: in order to avoid zombie processes (on unix),
              you may have to fetch the processes exitstatus with
              OperatingSystem>>getStatusOfProcess:aProcessId."

    self subclassResponsibility

    "Created: / 10.6.1998 / 12:00:26 / cg"
!

nameForSignal:aSignalNumber
    "for a given Unix signalnumber, return a descriptive string"

    aSignalNumber == self sigHUP    ifTrue:[^ 'hangup'].
    aSignalNumber == self sigINT    ifTrue:[^ 'interrupt'].
    aSignalNumber == self sigKILL   ifTrue:[^ 'kill'].
    aSignalNumber == self sigQUIT   ifTrue:[^ 'quit'].
    aSignalNumber == self sigILL    ifTrue:[^ 'illegal instruction'].
    aSignalNumber == self sigTRAP   ifTrue:[^ 'trap'].
    aSignalNumber == self sigABRT   ifTrue:[^ 'abort'].
    aSignalNumber == self sigIOT    ifTrue:[^ 'iot trap'].
    aSignalNumber == self sigEMT    ifTrue:[^ 'emt trap'].
    aSignalNumber == self sigFP     ifTrue:[^ 'fp exception'].
    aSignalNumber == self sigBUS    ifTrue:[^ 'bus error'].
    aSignalNumber == self sigSEGV   ifTrue:[^ 'segmentation violation'].
    aSignalNumber == self sigSYS    ifTrue:[^ 'bad system call'].
    aSignalNumber == self sigPIPE   ifTrue:[^ 'broken pipe'].
    aSignalNumber == self sigALRM   ifTrue:[^ 'alarm timer'].
    aSignalNumber == self sigTERM   ifTrue:[^ 'termination'].
    aSignalNumber == self sigSTOP   ifTrue:[^ 'stop'].
    aSignalNumber == self sigTSTP   ifTrue:[^ 'tty stop'].
    aSignalNumber == self sigCONT   ifTrue:[^ 'continue'].
    aSignalNumber == self sigCHLD   ifTrue:[^ 'child death'].
    aSignalNumber == self sigTTIN   ifTrue:[^ 'background tty input'].
    aSignalNumber == self sigTTOU   ifTrue:[^ 'background tty output'].
    aSignalNumber == self sigIO     ifTrue:[^ 'io available'].
    aSignalNumber == self sigXCPU   ifTrue:[^ 'cpu time expired'].
    aSignalNumber == self sigXFSZ   ifTrue:[^ 'file size limit'].
    aSignalNumber == self sigVTALRM ifTrue:[^ 'virtual alarm timer'].
    aSignalNumber == self sigPROF   ifTrue:[^ 'profiling timer'].
    aSignalNumber == self sigWINCH  ifTrue:[^ 'winsize changed'].
    aSignalNumber == self sigLOST   ifTrue:[^ 'resource lost'].
    aSignalNumber == self sigUSR1   ifTrue:[^ 'user signal 1'].
    aSignalNumber == self sigUSR2   ifTrue:[^ 'user signal 2'].
    aSignalNumber == self sigMSG    ifTrue:[^ 'HFT message'].
    aSignalNumber == self sigPWR    ifTrue:[^ 'power-fail'].
    aSignalNumber == self sigPRE    ifTrue:[^ 'programming exception'].
    aSignalNumber == self sigGRANT  ifTrue:[^ 'HFT access wanted'].
    aSignalNumber == self sigRETRACT ifTrue:[^ 'HFT access relinquish'].
    aSignalNumber == self sigSOUND   ifTrue:[^ 'HFT sound complete'].
    aSignalNumber == self sigDANGER  ifTrue:[^ 'low on paging space'].

    "notice: many systems map SIGPOLL and/or SIGUSR onto SIGIO
             therefore, keep SIGIO always above the two below" 
    aSignalNumber == self sigPOLL   ifTrue:[^ 'io available'].
    aSignalNumber == self sigURG    ifTrue:[^ 'urgent'].

    ^ 'unknown signal'

    "
     OperatingSystem nameForSignal:9
     OperatingSystem nameForSignal:(OperatingSystem sigPOLL) 
    "
!

operatingSystemSignal:signalNumber
    "return the signal to be raised when an 
     operatingSystem-signal occurs, or nil"

    OSSignals notNil ifTrue:[
        ^ OSSignals at:signalNumber ifAbsent:[nil]
    ].
    ^ nil
!

operatingSystemSignal:signalNumber install:aSignal
    "install a signal to be raised when an operatingSystem-signal occurs"

    OSSignals isNil ifTrue:[
        OSSignals := Array new:32
    ].
    OSSignals at:signalNumber put:aSignal
!

sendSignal:signalNumber to:processId
    "send a unix signal to some process (maybe myself).
     Returns false if any error occurred, true otherwise.

     Do not confuse UNIX signals with Smalltalk-Signals.

     WARNING: in order to avoid zombie processes (on unix),
              you may have to fetch the processes exitstatus with
              OperatingSystem>>getStatusOfProcess:aProcessId
              if the signal terminates that process."

    self subclassResponsibility
!

startSpyTimer
    "trigger a spyInterrupt, to be signalled after some short (virtual) time.
     Return true, if the spy-timerInterrupt was enabled.
     This was used by the old MessageTally for profiling.
     On systems, where no virtual timer is available, use the real timer
     (which is of course less correct).
     OBSOLETE: the new messageTally runs as a high prio process, not using 
               spy interrupts."

    ^ false
!

stopSpyTimer
    "stop spy timing - disable spy timer.
     OBSOLETE: the new messageTally runs as a high prio process, not using 
               spy interrupts."

    ^ false
!

terminateProcess:processId
    "terminate a unix process.
     The process has a chance to do some cleanup.

     WARNING: in order to avoid zombie processes (on unix),
              you may have to fetch the processes exitstatus with
              OperatingSystem>>getStatusOfProcess:aProcessId."

    self subclassResponsibility
!

terminateProcessGroup:processGroupId
    "terminate a unix process group.
     The process has a chance to do some cleanup.

     WARNING: in order to avoid zombie processes (on unix),
              you may have to fetch the processes exitstatus with
              OperatingSystem>>getStatusOfProcess:aProcessId."

    self subclassResponsibility
!

unblockInterrupts
    "enable interrupt processing - if any interrupts are pending,
     these will be handled immediately.
     When unblocking interrupts, take care of nested block/unblock
     calls - you must only unblock after a blockcall if they where
     really not blocked before. See OperatingSystemclass>>blockInterrupts."
%{
    __UNBLOCKINTERRUPTS();
    RETURN (nil);
%}
! !

!AbstractOperatingSystem class methodsFor:'misc'!

closePid:pid
    "free pid resource"

    self subclassResponsibility
!

exit
    "shutdown smalltalk immediately - this method does not return.
     Return 'good'-status (0) to the parent unix process."

    self exit:0.

    "OperatingSystem exit - dont evaluate this"
!

exit:exitCode
    "shutdown smalltalk immediately -
     returning an exit-code to the parent unix process."

%{  /* NOCONTEXT */
    int code = 1;

    if (__isSmallInteger(exitCode)) {
        code = __intVal(exitCode);
    }
    __mainExit(code);
%}
    "OperatingSystem exit:1 - dont evaluate this"
!

exitWithCoreDump
    "shutdown smalltalk immediately - dumping core.
     This always returns 'bad'-status to the parent unix process.
     Notice, that no cleanup is performed at all - you may have to
     manually remove any tempfiles.
     Use this only for debugging ST/X itself"

%{  /* NOCONTEXT */
    abort();
%}
    "
     OperatingSystem exitWithCoreDump - dont evaluate this
    "
! !

!AbstractOperatingSystem class methodsFor:'os queries'!

getCCDefine
    "return a string which was used to identify the C-Compiler used
     when STX was compiled, and which should be passed down when compiling methods.
     For example, on linux, this is '__GNUC__'; 
     on windows, this is either '__MSC__' or '__BORLANDC__'"

%{  /* NOCONTEXT */
#ifndef CC_DEFINE
# ifdef WIN32
#  ifdef __BORLANDC__
#   define CC_DEFINE    "__BORLANDC__"
#  else
#   define CC_DEFINE     "__MSC__"
#  endif
# else
#  ifdef __GNUC__
#   define CC_DEFINE     "__GNUC__"
#  else
#   define CC_DEFINE     "__CC__"
#  endif
# endif
#endif
    RETURN ( __MKSTRING(CC_DEFINE));
%}
    "
     OperatingSystem getCCDefine
    "
!

getCPUDefine
    "return a string which was used to identify this CPU type when STX was
     compiled, and which should be passed down when compiling methods.
     For example, on linux, this may be '-Di386'; on a vax, this would be '-Dvax'.
     This is normally not of interest to 'normal' users; however, it is passed
     down to the c-compiler when methods are incrementally compiled to machine code."

%{  /* NOCONTEXT */
#   ifndef CPU_DEFINE
#       define CPU_DEFINE "-DunknownCPU"
#   endif

    RETURN ( __MKSTRING(CPU_DEFINE));
%}
    "
     OperatingSystem getCPUDefine
    "
!

getCPUType
    "return a string giving the type of machine we're running on.
     Here, the machine for which ST/X was compiled is returned
     (i.e. for all x86's, the same i386 is returned).
     This may normally not be of any interest to you ..."

    |cpu|
    
%{  /* NOCONTEXT */

#   ifdef vax
#    define CPU_STRING "vax"
#   endif
#   ifdef mips
#    define CPU_STRING "mips"
#   endif
#   ifdef i386
#    define CPU_STRING "i386"
#   endif
#   ifdef i860
#    define CPU_STRING "i860"
#   endif
#   ifdef ns32k
#    define CPU_STRING "ns32k"
#   endif
#   ifdef mc68k
#    define CPU_STRING "mc68k"
#   endif
#   ifdef mc88k
#    define CPU_STRING "mc88k"
#   endif
#   ifdef sparc
#    define CPU_STRING "sparc"
#   endif
#   ifdef hppa
#    define CPU_STRING "hppa"
#   endif
#   ifdef rs6000
#    define CPU_STRING "rs6000"
#   endif
#   ifdef powerPC
#    define CPU_STRING "powerPC"
#   endif
#   ifdef alpha
#    define CPU_STRING "alpha"
#   endif
#   ifdef transputer
#    define CPU_STRING "transputer"
#   endif
#   ifdef ibm370
#    define CPU_STRING "ibm370"
#   endif

#   ifndef CPU_STRING
#    define CPU_STRING "unknown"
#   endif

    cpu = __MKSTRING(CPU_STRING);
#   undef CPU_STRING
%}.
    ^ cpu

    "
     OperatingSystem getCPUType
    "

    "examples: are we running on a ss-10/solaris ?"
    "
     (OperatingSystem getCPUType = 'sparc') 
     and:[OperatingSystem getOSType = 'solaris']
    "

    "or on a pc/solaris ?"
    "
     (OperatingSystem getCPUType = 'i386')
     and:[OperatingSystem getOSType = 'solaris']
    "
!

getDomainName
    "return the domain this host is in.
     Notice:
        not all systems support this; on some, 'unknown' is returned."

    self subclassResponsibility
!

getEnvironment:aStringOrSymbol
    "get an environment string"

    ^ self subclassResponsibility
!

getHostName
    "return the hostname we are running on - if there is
     a HOST environment variable, we are much faster here ...
     Notice:
        not all systems support this; on some, 'unknown' is returned."

    self subclassResponsibility
!

getLocaleInfo
    "return a dictionary filled with values from the locale information;
     Not all fields may be present, depending on the OS's setup and capabilities.
     Possible fields are:
        decimalPoint                    <String>

        thousandsSep                    <String>

        internationalCurrencySymbol     <String>

        currencySymbol                  <String>

        monetaryDecimalPoint            <String>

        monetaryThousandsSeparator      <String>

        positiveSign                    <String>

        negativeSign                    <String>

        internationalFractionalDigits   <Integer>

        fractionalDigits                <Integer>

        positiveSignPrecedesCurrencySymbol      <Boolean>

        negativeSignPrecedesCurrencySymbol      <Boolean>

        positiveSignSeparatedBySpaceFromCurrencySymbol  <Boolean>

        negativeSignSeparatedBySpaceFromCurrencySymbol  <Boolean>

        positiveSignPosition                            <Symbol>
                                                        one of: #parenthesesAround, 
                                                                #signPrecedes, 
                                                                #signSuceeds, 
                                                                #signPrecedesCurrencySymbol,
                                                                #signSuceedsCurrencySymbol

        negativeSignPosition                            <like above>

     it is up to the application to deal with undefined values.

     Notice, that (for now), the system does not use this information;
     it should be used by applications as required.
    "

    self subclassResponsibility
!

getOSDefine
    "return a string which was used to identify this machine when stx was
     compiled, and which should be passed down when compiling methods.
     For example, on linux, this is '-DLINUX'."

%{  /* NOCONTEXT */

#ifndef OS_DEFINE
# ifdef WIN32
#  define OS_DEFINE "-DWIN32"
# endif

# ifndef OS_DEFINE
#  define OS_DEFINE "-DunknownOS"
# endif
#endif

    RETURN ( __MKSTRING(OS_DEFINE));

#undef OS_DEFINE
%}
    "
     OperatingSystem getOSDefine
    "
!

getOSType
    "return a string giving the type of OS we're running on.
     This can be used to adapt programs to certain environment
     differences (for example: mail-lock strategy ...)"

    |os|

%{  /* NOCONTEXT */

#   ifdef MSDOS
#    define OS_STRING "msdos"
#   endif

#   ifdef WIN32
#    define OS_STRING "win32"
#   endif

#   ifdef MSWINDOWS
#    define OS_STRING "mswindows"
#   endif

#   ifdef VMS
#    ifdef __openVMS__
#     define OS_STRING "openVMS"
#    else
#     define OS_STRING "VMS"
#    endif
#   endif

#   ifdef MVS /* ;-) */
#    define OS_STRING "mvs"
#   endif

#   ifdef OS2
#    define OS_STRING "os2"
#   endif

#   ifdef sinix
#    define OS_STRING "sinix"
#   endif

#   ifdef ultrix
#    define OS_STRING "ultrix"
#   endif

#   ifdef sco
#    define OS_STRING "sco"
#   endif

#   ifdef hpux
#    define OS_STRING "hpux"
#   endif

#   ifdef LINUX
#    define OS_STRING "linux"
#   endif

#   ifdef sunos
#    define OS_STRING "sunos"
#   endif

#   ifdef solaris
#    define OS_STRING "solaris"
#   endif

#   ifdef IRIS
#    define OS_STRING "irix"
#   endif

#   ifdef aix
#    define OS_STRING "aix"
#   endif

#   ifdef realIX
#    define OS_STRING "realIX"
#   endif

#   ifdef __osf__
#    define OS_STRING "osf"
#   endif

    /*
     * no concrete info; become somewhat vague ...
     */
#   ifndef OS_STRING
#    ifdef MACH
#     define OS_STRING "mach"
#    endif
#   endif

#   ifndef OS_STRING
#    ifdef BSD
#     define OS_STRING "bsd"
#    endif

#    ifdef SYSV
#     ifdef SYSV3
#      define OS_STRING "sys5_3"
#     else
#      ifdef SYSV4
#       define OS_STRING "sys5_4"
#      else
#       define OS_STRING "sys5"
#      endif
#     endif
#    endif
#   endif

    /*
     * become very vague ...
     */
#   ifndef OS_STRING
#    ifdef POSIX
#     define OS_STRING "posix"
#    endif
#   endif
#   ifndef OS_STRING
#    ifdef UNIX
#     define OS_STRING "unix"
#    endif
#   endif

#   ifndef OS_STRING
#    define OS_STRING "unknown"
#   endif

    os = __MKSTRING(OS_STRING);

#   undef OS_STRING
%}.
    ^ os

    "
     OperatingSystem getOSType
    "
!

getProcessId
    "return the (unix-)processId"

    self subclassResponsibility
!

getSystemID
    "if supported by the OS, return the systemID;
     a unique per machine identification.
     WARNING:
        not all systems support this; on some, 'unknown' is returned."

    ^ 'unknown'

    "
     OperatingSystem getSystemID
    "
!

getSystemInfo
    "return info on the system weare running on.
     If the system supports the uname system call, that info is returned;
     otherwise, some simulated info is returned.
 
     WARNING:
       Do not depend on the amount and contents of the returned information, some
       systems may return more/less than others. Also, the contents depends on the
       OS, for example, linux returns 'ix86', while WIN32 returns 'x86'.

       This method is mainly provided to augment error reports with some system
       information. 
       (in case of system/version specific OS errors, conditional workarounds and patches
        may be based upon this info).
       Your application should NOT depend upon this in any way.

     The returned info may (or may not) contain:
        #system -> some operating system identification (irix, Linux, nt, win32s ...) 
        #version -> OS version (some os version identification)
        #release -> OS release (3.5, 1.2.1 ...)
        #node   -> some host identification (hostname)
        #domain  -> domain name (hosts domain)
        #machine -> type of machine (i586, mips ...)
    "

    |info|

    info := IdentityDictionary new.
    info at:#system put:(self getSystemType).
    info at:#node put:(self getHostName).
    info at:#machine put:(self getCPUType).
    info at:#architecture put:'unknown'.
    info at:#domain put:self getDomainName.
    info at:#osType put:(self getOSType).
    ^ info

    "
     OperatingSystem getSystemInfo
    "
!

getSystemType
    "return a string giving the type of system we're running on.
     This is almost the same as getOSType, but the returned string
     is slightly different for some systems (i.e. iris vs. irix).
     Dont depend on this - use getOSType. I dont really see a point
     here ... 
     (except for slight differences between next/mach and other machs)"

    ^ self getOSType

    "
     OperatingSystem getSystemType
    "
!

getWindowsDirectory
    "internal interface - only for Windows based systems.
     Return the windows directory 
     (which - depending on the system - may be \WINNT, \WINDOWS or whatever)
     On non-windows systems, nil is returned."

    ^ nil

    "
     OperatingSystem getWindowsDirectory
    "
!

getWindowsSystemDirectory
    "internal interface - only for Windows based systems.
     Return the windows system directory 
     (which - depending on the system - may be \WINNT\SYSTEM32, 
      \WINDOWS\SYSTEM or whatever)
     On non-windows systems, nil is returned."

    ^ nil

    "
     OperatingSystem getWindowsSystemDirectory
    "
!

hasConsole
    "return true, if there is some kind of console available
     (i.e. for proper stdIn, stdOut and stdErr handling).
     This only returns false when running under windows, and
     the system is running as a pure windows application.
     If false, the miniDebugger is useless and not used."

    ^ true
!

isBSDlike
    "return true, if the OS we're running on is a 'real' unix."

    ^ false
!

isMAClike
    "return true, if running on a macOS (but not on A/UX)"

    ^ false
!

isMSDOSlike
    "return true, if the OS we're running on is msdos like 
     (in contrast to unix-like).
     This returns true for any of msdos, win32s, win95,
     winNT and os/2."

    ^ false
!

isMSWINDOWSNTlike
    "This returns true if running in a Windows-NT system."

     ^ false.
!

isMSWINDOWSlike
    "return true, if running on a MS-Windows like system.
     This returns true for any of win32s, win95 and winNT."

    ^ false
!

isOS2like
    "return true, if the OS we're running on is OS2 like.
     Only returns true for a plain OS/2 system."

    ^ false
!

isUNIXlike
    "return true, if the OS we're running on is a unix like."

    ^ false
!

isVMSlike
    "return true, if the OS we're running in is VMS (or openVMS)."

    ^ false
!

maxFileNameLength
    "return the max number of characters in a filename.
     CAVEAT:
         Actually, the following is somewhat wrong - some systems
         support different sizes, depending on the volume.
         We return a somewhat conservative number here.
         Another entry, to query for volume specific max
         will be added in the future."

    self subclassResponsibility
!

maxPathLength
    "return the max number of characters in a pathName."

    self subclassResponsibility
!

pathSeparator
    "return the character which separates items in the PATH variable"

    self subclassResponsibility
!

platformName
    "return a string describing the OS platform very we're running on.
     This returns #unix for all unix derivatives.
     I.e. it is much less specific than getOSType or getSystemType."

    |os|

    os := self getSystemType.
    os = 'win32' ifTrue:[ ^ #win32].
    os = 'os2' ifTrue:[ ^ #os2].
    os = 'macos' ifTrue:[ ^ #mac].
    os = 'VMS' ifTrue:[ ^ #vms].
    os = 'openVMS' ifTrue:[ ^ #vms].
    ^ #unix

    "
     OperatingSystem platformName
    "

    "Modified: 20.6.1997 / 17:37:26 / cg"
!

setLocaleInfo:anInfoDictionary
    "set the locale information; if set, this oerrides the OS's settings.
     (internal in ST/X only - the OS's settings remain unaffected)
     See description of fields in #getLocaleInfo.

     Notice, that (for now), the system does not use this information;
     it should be used by applications as required."

    LocaleInfo := anInfoDictionary

    "
     |d|

     d := IdentityDictionary new.
     d at:#decimalPoint                 put:'.'         .
     d at:#thousandsSeparator           put:','         .
     d at:#currencySymbol               put:'USD'       .
     d at:#monetaryDecimalPoint         put:'.'         .
     d at:#monetaryThousandsSeparator   put:'.'         .
     d at:#fractionalDigits             put:2           .
     d at:#positiveSign                 put:'+'         .
     d at:#negativeSign                 put:'-'         .
     d at:#positiveSignPrecedesCurrencySymbol put:true          .
     d at:#negativeSignPrecedesCurrencySymbol put:false         .
     OperatingSystem setLocaleInfo:d
    "
!

supportsChildInterrupts
    "return true, if the OS supports childProcess termination signalling
     through interrupts (i.e. SIGCHILD)"

    ^ false

    "
     OperatingSystem supportsChildInterrupts 
    "
!

supportsFileOwnerGroups
    "return true, if the OS's file system supports file
     group ownership - here, we are optimistic assuming that
     we are running under a real OS.
     Redefined in Win32OS to return false."

    ^ true

    "Modified: / 10.9.1998 / 17:48:20 / cg"
    "Created: / 10.9.1998 / 17:56:28 / cg"
!

supportsFileOwners
    "return true, if the OS's file system supports file
     ownership - here, we are optimistic assuming that
     we are running under a real OS.
     Redefined in Win32OS to return false."

    ^ true

    "Modified: / 10.9.1998 / 17:48:20 / cg"
    "Created: / 10.9.1998 / 17:56:11 / cg"
!

supportsIOInterrupts
    "return true, if the OS supports IO availability interrupts 
     (i.e. SIGPOLL/SIGIO)."

    ^ false

    "
     OperatingSystem supportsIOInterrupts 
    "
!

supportsNonBlockingIO
    "return true, if the OS supports nonblocking IO."

    ^ false

    "
     OperatingSystem supportsNonBlockingIO  
    "
!

supportsSelect
    "return true, if the OS supports selecting on multiple
     filedescriptors via select.
     If false is returned, ProcessorScheduler will poll in 50ms
     intervals for I/O becoming ready."

    ^ true

    "
     OperatingSystem supportsSelect 
    "
!

supportsSelectOnPipes
    "return true, if the OS supports selecting on pipe
     filedescriptors via select.
     If false is returned, ProcessorScheduler will poll in 50ms
     intervals for I/O becoming ready."

    ^ true

    "
     OperatingSystem supportsSelectOnPipes 
    "

    "Modified: / 14.12.1999 / 19:40:32 / cg"
    "Created: / 14.12.1999 / 19:43:43 / cg"
!

supportsSelectOnSockets
    "return true, if the OS supports selecting on socket
     filedescriptors via select.
     If false is returned, ProcessorScheduler will poll in 50ms
     intervals for I/O becoming ready."

    ^ true

    "
     OperatingSystem supportsSelectOnSockets 
    "

    "Modified: / 14.12.1999 / 19:40:32 / cg"
!

supportsVolumes
    "return true, if the OS supports disk volumes.
     False is returned for UNIX, true for MSDOS and VMS"

    ^ false

    "Created: / 29.10.1998 / 13:20:37 / cg"
! !

!AbstractOperatingSystem class methodsFor:'path queries'!

defaultPackagePath
    "return a default packagePath - thats a collection of
     dirnames, where ST/X searches for its package subdirs.
     This method might be redefined in concrete OS's to add
     OS-specific directory names."

    |pPath p homePath priv userPrivateSTXDir|

    "
     the path is set to search files first locally
     - this allows private stuff to override global stuff
    "
    pPath := OrderedCollection new.

    "/
    "/ the current (default) directory
    "/
    pPath add:(Filename currentDirectory name).

    "/
    "/ the users home (login) directory
    "/
    homePath := OperatingSystem getHomeDirectory.
    homePath notNil ifTrue:[
        (pPath includes:homePath) ifFalse:[
            pPath add:homePath.
        ].

        "/
        "/ a users private smalltalk directory in its home (login) directory
        "/
        OperatingSystem isUNIXlike ifTrue:[
            priv := '.smalltalk'.
        ] ifFalse:[
            priv := 'smalltalk'.
        ].
        userPrivateSTXDir := homePath asFilename constructString:priv.
        (userPrivateSTXDir asFilename isDirectory) ifTrue:[
            (pPath includes:userPrivateSTXDir) ifFalse:[
                pPath add:userPrivateSTXDir
            ]
        ].
    ].                                                              

    "/
    "/ STX_TOPDIR from the environment
    "/
    p := OperatingSystem getEnvironment:'STX_TOPDIR'.
    p notNil ifTrue:[
        (pPath includes:p) ifFalse:[
            pPath add:p
        ].
    ].
    pPath add:'/opt/smalltalk'.
    pPath := pPath select:[:p | (p asFilename construct:'packages') exists].
    pPath := pPath collect:[:p | (p asFilename constructString:'packages')].

   (p := OperatingSystem getEnvironment:'STX_PACKAGEPATH') notNil ifTrue:[
        p := p asCollectionOfSubstringsSeparatedBy:$:.
        p reverseDo:[:dir|
            (pPath includes:dir) ifFalse:[
                pPath addFirst:dir.
            ].
        ].
    ].

    ^ pPath

    "
     self defaultPackagePath
    "

    "Modified: / 24.12.1999 / 00:31:29 / cg"
!

defaultSystemPath
    "return a default systemPath - thats a collection of
     dirnames, where ST/X searches for its files.
     This method is redefined in concrete OS's to add
     OS-specific directory names."

    |sysPath p homePath priv userPrivateSTXDir|

    "
     the path is set to search files first locally
     - this allows private stuff to override global stuff
    "
    sysPath := OrderedCollection new.

    "/
    "/ the current (default) directory
    "/
    sysPath add:(Filename currentDirectory name).

    "/
    "/ the users home (login) directory
    "/
    homePath := OperatingSystem getHomeDirectory.
    homePath notNil ifTrue:[
"/ NO LONGER
"/        (sysPath includes:homePath) ifFalse:[
"/            sysPath add:homePath.
"/        ].
"/
        "/
        "/ a users private smalltalk directory in its home (login) directory
        "/
        OperatingSystem isUNIXlike ifTrue:[
            priv := '.smalltalk'.
        ] ifFalse:[
            priv := 'smalltalk'.
        ].
        userPrivateSTXDir := homePath asFilename constructString:priv.
        (userPrivateSTXDir asFilename isDirectory) ifTrue:[
            (sysPath includes:userPrivateSTXDir) ifFalse:[
                sysPath add:userPrivateSTXDir
            ]
        ].
    ].

    "/
    "/ SMALLTALK_LIBDIR, STX_LIBDIR and STX_TOPDIR from the environment
    "/
    #( 'SMALLTALK_LIBDIR'
       'STX_LIBDIR'
        'STX_TOPDIR'
     ) do:[:each |
        p := OperatingSystem getEnvironment:each.
        p notNil ifTrue:[
            (sysPath includes:p) ifFalse:[
                sysPath add:p
            ]
        ].
    ].
    ^ sysPath

    "Modified: / 24.12.1999 / 00:30:27 / cg"
! !

!AbstractOperatingSystem class methodsFor:'private'!

osProcessStatusClass
    ^ self subclassResponsibility

    "Created: / 12.6.1998 / 16:30:29 / cg"
! !

!AbstractOperatingSystem class methodsFor:'shared memory access'!

shmAttach:id address:addr flags:flags
    "low level entry to shmat()-system call.
     Not supported on all operatingSystems"

    ^ UnsupportedOperationSignal raise

    "Modified: / 19.5.1999 / 14:21:35 / cg"
!

shmDetach:addr
    "low level entry to shmdt()-system call.
     Not supported on all operatingSystems"

    ^ UnsupportedOperationSignal raise

    "Modified: / 19.5.1999 / 14:21:37 / cg"
!

shmGet:key size:size flags:flags
    "low level entry to shmget()-system call.
     This is not for public use and not supported with all operatingSystems.
     - use the provided wrapper class SharedExternalBytes instead."

    ^ UnsupportedOperationSignal raise

    "Modified: / 19.5.1999 / 14:21:41 / cg"
! !

!AbstractOperatingSystem class methodsFor:'time and date'!

computeDatePartsOf:osTime for:aBlock
    "compute year, month and day from the OS time, osTime
     and evaluate the argument, a 3-arg block with these.
     Conversion is to localtime including any daylight saving adjustments."

    self subclassResponsibility
!

computeOSTimeFromUTCYear:y month:m day:d hour:h minute:min second:s millisecond:millis
    "return the OS-dependent time for the given time and day. 
     The arguments are assumed to be in UTC Time"

    self subclassResponsibility

    "Created: / 13.7.1999 / 12:44:03 / stefan"
!

computeOSTimeFromYear:y month:m day:d hour:h minute:min seconds:s millis:millis
    "return the OS-dependent time for the given time and day. 
     The arguments are assumed to be in localtime including
     any daylight saving adjustings."

    self subclassResponsibility
!

computeTimeAndDateFrom:osTime
    "given an OS-dependent time in osTime, return an Array
     containing (full-) year, month, day, hour, minute and seconds,
     offset to UTC, daylight savings time flag, milliseconds,
     dayInYear (1..) and dayInWeek (1..).
     Conversion is to localtime including any daylight saving adjustments."

    self subclassResponsibility
!

computeTimePartsOf:osTime for:aBlock
    "compute hours, minutes, seconds and milliseconds from the osTime 
     and evaluate the argument, a 4-arg block with these.
     Conversion is to localtime including any daylight saving adjustments."

    self subclassResponsibility
!

computeUTCTimeAndDateFrom:osTime
    "given an OS-dependent time in osTime, return an Array
     containing year, month, day, hour, minute and seconds,
     offset to UTC, daylight savings time flag, milliseconds,
     dayInYear (1..) and dayInWeek (1..).
     Conversion is to UTC."

    self subclassResponsibility
!

computeUTCTimePartsOf:osTime for:aBlock
    "compute hours, minutes, seconds and milliseconds from the osTime 
     and evaluate the argument, a 4-arg block with these.
     Conversion is to UTC."

    self subclassResponsibility
!

getMicrosecondTime
    "This returns the microsecond timers value - if available. 
     On some machines, times with this precision may not be available,
     on those, the returned value may be rounded towards some internal
     clock resolution value."

    "/ fallBack - use getMillisecondTime, which must be implemented
    "/ for all OS's

    ^ self getMillisecondTime * 1000

    "Created: / 30.7.1998 / 16:38:26 / cg"
!

getMillisecondTime
    "This returns the millisecond timers value. 
     The range is limited to 0..1fffffff (i.e. the SmallInteger range) to avoid
     LargeInteger arithmetic when doing timeouts and delays.
     Since this value is wrapping around in regular intervals, this can only be used for 
     short relative time deltas.
     Use the millisecondTimeXXX:-methods to compare and add time deltas - these know about the wrap.

     BAD DESIGN:
        This should be changed to return some instance of RelativeTime,
        and these computations moved there.

     Dont use this method in application code since it is an internal (private)
     interface. For compatibility with ST-80, use Time millisecondClockValue.
    "

    self subclassResponsibility
!

getOSTime
    "This returns the OS time.
     The base of the returned value is not consistent across
     different OS's - some return the number of millis since jan, 1st 1970;
     others since 1900. The Time classes are prepared for this, and 
     converts as appropriate (by using my fromOSTime: conversion methods).

     Dont use this method in application code since it is an internal (private)
     interface. For compatibility with ST-80, use Time>>millisecondClockValue.
     or use instances of Time, Date or AbsoluteTime to work with.
    "

    self subclassResponsibility
!

maximumMillisecondTimeDelta
    "this returns the maximum delta supported by millisecondCounter
     based methods. The returned value is half the value at which the
     timer wraps."

%{  /* NOCONTEXT */
    RETURN ( __MKSMALLINT(0x0FFFFFFF) );
%}
!

millisecondDelay:millis
    "delay execution for millis milliseconds or until the next event
     arrives.
     All lower priority threads will also sleep for the duration, 
     interrupts (and therefore, higher prio processes) are
     still handled. 
     Better use a Delay, to only delay the calling thread.
     (however, a delay cannot be used in the event handler or scheduler)"

    |now then delta|

    now := self getMillisecondTime.
    then := self millisecondTimeAdd:now and:millis.

    [self millisecondTime:then isAfter:now] whileTrue:[
        delta := self millisecondTimeDeltaBetween:then and:now.
        self selectOnAnyReadable:nil writable:nil exception:nil withTimeOut:delta.
        now := self getMillisecondTime.
    ]

    "
     OperatingSystem millisecondDelay:2000
    "
!

millisecondTime:msTime1 isAfter:msTime2
    "return true if msTime1 is after msTime2, false if not.
     The two arguments are supposed to be millisecond times 
     (such as returned getMillisecondTime) which wrap at 16r1FFFFFFF.

     This should really be moved to some RelativeTime class."

    (msTime1 > msTime2) ifTrue:[
        ((msTime1 - msTime2) >= 16r10000000) ifTrue:[
            ^ false
        ].
        ^ true
    ].
    ((msTime2 - msTime1) > 16r10000000) ifTrue:[
        ^ true
    ].
    ^ false
!

millisecondTimeAdd:msTime1 and:msTime2
    "Add two millisecond times (such as returned getMillisecondTime).
     The returned value is msTime1 + msTime2 where a wrap occurs at:16r1FFFFFFF.

     This should really be moved to some RelativeTime class."

    |sum|

    sum := msTime1 + msTime2.
    (sum > 16r1FFFFFFF) ifTrue:[^ sum - 16r20000000].
    (sum < 0) ifTrue:[^ sum + 16r20000000].
    ^ sum
!

millisecondTimeDeltaBetween:msTime1 and:msTime2
    "subtract two millisecond times (such as returned getMillisecondTime)
     and return the difference. Since milli-times wrap (at 16r01FFFFFFF), 
     some special handling is built-in here.
     The returned value is msTime1 - msTime2. The returned value is invalid
     if the delta is >= 0x10000000.

     This should really be moved to some RelativeTime class;
     better yet: create a subclass of Integer named LimitedRangeInteger."

    (msTime1 > msTime2) ifTrue:[
        ^ msTime1 - msTime2
    ].
    ^ msTime1 + 16r10000000 - msTime2

    "
     OperatingSystem millisecondTimeAdd:16r0FFFFFFF and:1   
     OperatingSystem millisecondTimeAdd:16r0FFFFFFF and:(16 / 3)  
     OperatingSystem millisecondTimeAdd:16r0FFFFFFF and:1000   

     OperatingSystem millisecondTimeDeltaBetween:0 and:16r0FFFFFFF  
     OperatingSystem millisecondTimeDeltaBetween:(13/3) and:16r0FFFFFFF     
     OperatingSystem millisecondTimeDeltaBetween:999 and:16r0FFFFFFF       

     OperatingSystem millisecondTime:0 isAfter:16r0FFFFFFF    
     OperatingSystem millisecondTime:(13/3) isAfter:16r0FFFFFFF   
     OperatingSystem millisecondTime:999 isAfter:16r0FFFFFFF       

     OperatingSystem millisecondTime:0 isAfter:0          
     OperatingSystem millisecondTime:(13/3) isAfter:0  
     OperatingSystem millisecondTime:999 isAfter:0       

     OperatingSystem millisecondTime:1 isAfter:0        
     OperatingSystem millisecondTime:(13/3) isAfter:2
     OperatingSystem millisecondTime:999 isAfter:900       

     |t1 t2|

     t1 := Time millisecondClockValue.
     (Delay forMilliseconds:1) wait.   
     t2 := Time millisecondClockValue.
     OperatingSystem millisecondTimeDeltaBetween:t2 and:t1 
    "
!

sleep:numberOfSeconds
    "{ Pragma: +optSpace }"

    "cease ANY action for some time. This suspends the whole smalltalk
     (unix-) process for some time.
     Not really useful since not even low-prio processes and interrupt
     handling will run during the sleep.
     Use either OperatingSystem>>millisecondDelay: (which makes all
     threads sleep, but handles interrupts) or use a Delay (which makes
     only the calling thread sleep)."

    self subclassResponsibility
! !

!AbstractOperatingSystem class methodsFor:'users & groups'!

getEffectiveGroupID
    "{ Pragma: +optSpace }"

    "return the current users (thats you) effective numeric group id.
     This is only different from getGroupID, if you have ST/X running
     as a setuid program (of which you should think about twice)."

    ^ self getGroupID

    "
     OperatingSystem getEffectiveGroupID
    "
!

getEffectiveUserID
    "{ Pragma: +optSpace }"

    "return the current users (thats you) effective numeric user id.
     This is only different from getUserID, if you have ST/X running
     as a setuid program (of which you should think about twice)."

    ^ self getUserID

    "
     OperatingSystem getEffectiveUserID
    "
!

getFullUserName
    "{ Pragma: +optSpace }"

    "return a string with the users full name (thats you) - if available.
     If not, return the login name as a fallBack."

    ^ self getFullUserNameFromID:(self getUserID)

    "
     OperatingSystem getFullUserName 
    "

    "Modified: 24.1.1997 / 11:31:55 / cg"
!

getFullUserNameFromID:userID
    "{ Pragma: +optSpace }"

    "return a string with the users full name - if available.
     If not, return the login name as a fallBack."

    ^ self getUserNameFromID:userID

    "
     OperatingSystem getFullUserNameFromID:0 
     OperatingSystem getFullUserNameFromID:(OperatingSystem getUserID)  

     OperatingSystem getUserNameFromID:(OperatingSystem getUserID)  
    "

    "Modified: 15.7.1996 / 12:44:21 / cg"
!

getGroupID
    "{ Pragma: +optSpace }"

    "return the current users (thats you) numeric group id"

    ^ 1 "/ just a dummy for systems which do not have userIDs

    "
     OperatingSystem getGroupID
    "
!

getGroupNameFromID:aNumber
    "{ Pragma: +optSpace }"

    "return the group-name-string for a given numeric group-id"

    ^ '???' "/ just a dummy for systems which do not have groups

    "
     OperatingSystem getGroupNameFromID:0
     OperatingSystem getGroupNameFromID:10
    "
!

getHomeDirectory
    "{ Pragma: +optSpace }"

    "return the name of the users home directory
     (i.e. yours)"

    ^ self getEnvironment:'HOME'

    "
     OperatingSystem getHomeDirectory
    "

    "Modified: 24.1.1997 / 11:32:13 / cg"
!

getLoginName
    "{ Pragma: +optSpace }"

    "return a string with the users login name (thats yours)"

    self subclassResponsibility
!

getUserID
    "{ Pragma: +optSpace }"

    "return the current users (thats you) numeric user id"

    ^ 1 "just a dummy for systems which do not have userIDs"

    "
     OperatingSystem getUserID
    "
!

getUserNameFromID:aNumber
    "{ Pragma: +optSpace }"

    "return the user-name-string for a given numeric user-id.
     This is the login name, not the fullName."

    "/ fallBack dummy

    aNumber == self getUserID ifTrue:[
        ^ self getLoginName
    ].

    ^ '? (' , aNumber printString , ')'

    "
     OperatingSystem getUserNameFromID:0
     OperatingSystem getUserNameFromID:100
     OperatingSystem getUserNameFromID:9991 
    "
!

userInfoOf:aNameOrID
    "{ Pragma: +optSpace }"

    "return a dictionary filled with userinfo. The argument can be either
     a string with the users name or its numeric id.
     Notice, that not all systems provide (all of) this info;
     DOS systems return nothing; 
     non-SYSV4 systems have no age/comment.
     Portable applications may want to check the systemType and NOT depend
     on all keys to be present in the returned dictionary.
     Another notice: on some systems (SYSV4), the gecos field includes multiple
     entries (i.e. not just the name), separated by commas. You may want to
     extract any substring, up to the first comma to get the real life name."

    |info|

    "/ fallBack dummy
    info := IdentityDictionary new.
    info at:#name put:(self getLoginName).
    info at:#dir put:(self getHomeDirectory).
    ^ info

    "
     OperatingSystem userInfoOf:'root'
     OperatingSystem userInfoOf:1
     OperatingSystem userInfoOf:'claus' 
     OperatingSystem userInfoOf:'fooBar' 
     OperatingSystem userInfoOf:(OperatingSystem getUserID)
    "
! !

!AbstractOperatingSystem class methodsFor:'waiting for events'!

blockingChildProcessWait
     "return true, if childProcessWait: blocks, if no children are ready.
      On those systems, we must be somewhat careful when looking out for
      a subprocesses status (to avoid blocking)."

    ^ true
!

childProcessWait:blocking pid:pidToWait
    "{ Pragma: +optSpace }"

    "get status changes from child processes.
     Return an OSProcessStatus or nil, if no process has terminated.
     If blocking is true, we wait until a process changed state, 
     otherwise we return immediately.
     Note that win32 needs to know the HANDLE of the process on which 
     it waits.  In case of an error, THIS ALWAYS WAITS and then times out."

    self subclassResponsibility
!

numAvailableForReadOn:fd
    "return the number of bytes available for reading, without blocking."

    "/ fallBack for systems which do not provide this info
    ^ (self readCheck:fd) ifTrue:[1] ifFalse:[0]
!

readCheck:fd
    "return true, if data is available on a filedescriptor 
     (i.e. read is possible without blocking).
     This depends on a working select or FIONREAD to be provided by the OS."

    self supportsSelect ifFalse:[
        "/ mhmh - what should we do then ?
        "/ For now, return true as if data was present,
        "/ and let the thread fall into the read.
        "/ It will then (hopefully) be desceduled there and
        "/ effectively polling for input.

        ^ true
    ].

    (self selectOnAnyReadable:(Array with:fd)
                     writable:nil
                    exception:nil
                  withTimeOut:0) == fd
        ifTrue:[^ true].
    ^ false
!

readWriteCheck:fd
    "return true, if filedescriptor can be read or written without blocking.
     This is actually only used with sockets, to wait for a connect to
     be finished."

    self supportsSelect ifFalse:[
        "/ mhmh - what should we do then ?
        "/ For now, return true as if data was present,
        "/ and let the thread fall into the write.
        "/ It will then (hopefully) be desceduled there and
        "/ effectively polling for output.
        ^ true
    ].

    (self selectOnAnyReadable:(Array with:fd)
                     writable:(Array with:fd)
                    exception:nil
                  withTimeOut:0) == fd
        ifTrue:[^ true].
    ^ false
!

selectOn:fd1 and:fd2 withTimeOut:millis
    "wait for any fd to become ready; timeout after t milliseconds.
     A zero timeout-time will immediately return (i.e. poll).
     Return fd if i/o ok, nil if timed-out or interrupted.
     Obsolete:
        This is a leftover method and will vanish."

    ^ self selectOnAnyReadable:(Array with:fd1 with:fd2)
                      writable:(Array with:fd1 with:fd2)
                     exception:nil
                   withTimeOut:millis
!

selectOn:fd withTimeOut:millis
    "wait for aFileDesriptor to become ready; timeout after t milliseconds.
     Return true, if i/o ok, false if timed-out or interrupted.
     With 0 as timeout argument, this can be used to check for availability
     of read-data.
     Experimental."

    ^ self selectOnAnyReadable:(Array with:fd)
                      writable:(Array with:fd)
                     exception:nil
                   withTimeOut:millis
!

selectOnAny:fdArray withTimeOut:millis
    "wait for any fd in fdArray (an Array of integers) to become ready;
     timeout after t milliseconds. An empty set will always wait.
     Return first ready fd if i/o ok, nil if timed-out or interrupted.
     Experimental."

    ^ self selectOnAnyReadable:fdArray
                      writable:fdArray
                     exception:nil
                   withTimeOut:millis
!

selectOnAnyReadable:fdArray withTimeOut:millis
    "wait for any fd in fdArray (an Array of integers) to become ready for 
     reading. Timeout after t milliseconds. An empty set will always wait.
     A zero timeout-time will immediately return (i.e. poll).
     Return first ready fd if i/o ok, nil if timed-out or interrupted.
     Experimental."

    ^ self selectOnAnyReadable:fdArray 
                      writable:nil 
                     exception:nil
                   withTimeOut:millis
!

selectOnAnyReadable:readFdArray writable:writeFdArray exception:exceptFdArray withTimeOut:millis
    "wait for any fd in readFdArray (an Array of integers) to become ready for 
     reading, writeFdArray to become ready for writing, or exceptFdArray to 
     arrive exceptional data (i.e. out-of-band data).
     Timeout after t milliseconds or, if the timeout time is 0, immediately..
     Empty fd-sets will always wait. Zero time can be used to poll file-
     descriptors (i.e. to check if I/O possible without blocking).
     Return first ready fd if I/O ok, nil if timed-out or interrupted."

    self subclassResponsibility
!

setBlocking:aBoolean on:fd
    "{ Pragma: +optSpace }"

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

    self subclassResponsibility
!

writeCheck:fd
    "return true, if filedescriptor can be written without blocking"

    self supportsSelect ifFalse:[
        "/ mhmh - what should we do then ?
        "/ For now, return true as if data was present,
        "/ and let the thread fall into the write.
        "/ It will then (hopefully) be desceduled there and
        "/ effectively polling for output.
        ^ true
    ].

    (self selectOnAnyReadable:nil
                     writable:(Array with:fd)
                    exception:nil
                  withTimeOut:0) == fd
        ifTrue:[^ true].
    ^ false
! !

!AbstractOperatingSystem class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.53 2001-12-11 15:07:01 cg Exp $'
! !
AbstractOperatingSystem initialize!