shuffler does a readWait, to be responsive when reading
authorpenk
Fri, 02 Aug 2002 16:22:33 +0200
changeset 6706 d0c8dfdf57e6
parent 6705 490a44b0890d
child 6707 790fc577c403
shuffler does a readWait, to be responsive when reading from a pipe (christians archive application)
AbstractOperatingSystem.st
--- a/AbstractOperatingSystem.st	Fri Aug 02 16:10:02 2002 +0200
+++ b/AbstractOperatingSystem.st	Fri Aug 02 16:22:33 2002 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
-	      All Rights Reserved
+              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
@@ -13,12 +13,12 @@
 "{ Package: 'stx:libbasic' }"
 
 Object subclass:#AbstractOperatingSystem
-	instanceVariableNames:''
-	classVariableNames:'ConcreteClass LastErrorNumber LocaleInfo OSSignals PipeFailed
-		ErrorSignal AccessDeniedErrorSignal FileNotFoundErrorSignal
-		InvalidArgumentsSignal UnsupportedOperationSignal Resources'
-	poolDictionaries:''
-	category:'System-Support'
+        instanceVariableNames:''
+        classVariableNames:'ConcreteClass LastErrorNumber LocaleInfo OSSignals PipeFailed
+                ErrorSignal AccessDeniedErrorSignal FileNotFoundErrorSignal
+                InvalidArgumentsSignal UnsupportedOperationSignal Resources'
+        poolDictionaries:''
+        category:'System-Support'
 !
 
 !AbstractOperatingSystem class methodsFor:'documentation'!
@@ -26,7 +26,7 @@
 copyright
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
-	      All Rights Reserved
+              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
@@ -45,108 +45,108 @@
     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
+        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
+        Claus Gittinger
 
     [see also:]
-	OSProcessStatus
-	Filename Date Time
-	ExternalStream FileStream PipeStream Socket
+        OSProcessStatus
+        Filename Date Time
+        ExternalStream FileStream PipeStream Socket
 "
 !
 
 examples
 "
   various queries
-								[exBegin]
+                                                                [exBegin]
     Transcript 
-	showCR:'hello ' , (OperatingSystem getLoginName)
-								[exEnd]
-
-								[exBegin]
+        showCR:'hello ' , (OperatingSystem getLoginName)
+                                                                [exEnd]
+
+                                                                [exBegin]
     OperatingSystem isUNIXlike ifTrue:[
-	Transcript showCR:'this is some UNIX-like OS'
+        Transcript showCR:'this is some UNIX-like OS'
     ] ifFalse:[
-	Transcript showCR:'this OS is not UNIX-like'
+        Transcript showCR:'this OS is not UNIX-like'
     ]
-								[exEnd]
-
-								[exBegin]
+                                                                [exEnd]
+
+                                                                [exBegin]
     Transcript 
-	showCR:'this machine is called ' , OperatingSystem getHostName
-								[exEnd]
-
-								[exBegin]
+        showCR:'this machine is called ' , OperatingSystem getHostName
+                                                                [exEnd]
+
+                                                                [exBegin]
     Transcript 
-	showCR:('this machine is in the '
-	       , OperatingSystem getDomainName
-	       , ' domain')
-								[exEnd]
-
-								[exBegin]
+        showCR:('this machine is in the '
+               , OperatingSystem getDomainName
+               , ' domain')
+                                                                [exEnd]
+
+                                                                [exBegin]
     Transcript 
-	showCR:('this machine''s CPU is a '
-	       , OperatingSystem getCPUType
-	       )
-								[exEnd]
-
-								[exBegin]
+        showCR:('this machine''s CPU is a '
+               , OperatingSystem getCPUType
+               )
+                                                                [exEnd]
+
+                                                                [exBegin]
     Transcript showCR:'executing ls command ...'.
     OperatingSystem executeCommand:'ls'.
     Transcript showCR:'... done.'.
-								[exEnd]
+                                                                [exEnd]
 
   locking a file 
   (should be executed on two running smalltalks - not in two threads):
-								[exBegin]
+                                                                [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.
+        '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]
+                                                                [exBegin]
 "
 ! !
 
@@ -162,25 +162,25 @@
     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'.
+        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
 !
@@ -190,21 +190,21 @@
 
     osType := self getSystemType.
     osType = 'win32' ifTrue:[
-	cls := Win32OperatingSystem
+        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
-		]
-	    ]
-	]
+        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.
 ! !
@@ -556,7 +556,7 @@
 
 update:something with:aParameter from:changedObject
     ((something == #Language) or:[something == #LanguageTerritory]) ifTrue:[
-	self initResources
+        self initResources
     ]
 ! !
 
@@ -566,7 +566,7 @@
     "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."
+             environment - this interface will change."
 
     LastErrorNumber := nil.
 
@@ -611,7 +611,7 @@
      (as kept in an osErrorHolder)."
 
     Resources isNil ifTrue:[
-	^ errorSymbol
+        ^ errorSymbol
     ].
     ^ Resources at:errorSymbol ifAbsent:errorSymbol
 
@@ -631,8 +631,8 @@
     holder := self errorHolderForNumber:errNr.
     errSym := holder errorSymbol.
     ^ Array 
-	with:errSym 
-	with:(self errorStringForSymbol:errSym)
+        with:errSym 
+        with:(self errorStringForSymbol:errSym)
 
     "
      OperatingSystem errorSymbolAndTextForNumber:(OperatingSystem errorNumberFor:#EPERM)  
@@ -671,7 +671,7 @@
     "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."
+             environment - this interface will change."
 
     ^ LastErrorNumber
 
@@ -684,7 +684,7 @@
     "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."
+             environment - this interface will change."
 
     LastErrorNumber isNil ifTrue:[^ nil].
     ^ self errorTextForNumber:LastErrorNumber
@@ -698,7 +698,7 @@
     "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."
+             environment - this interface will change."
 
     LastErrorNumber isNil ifTrue:[^ nil].
     ^ self errorSymbolForNumber:LastErrorNumber
@@ -742,14 +742,14 @@
      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
+        exec:aCommandPath 
+        withArguments:argArray
+        environment:nil
+        fileDescriptors:nil
+        closeDescriptors:nil 
+        fork:false 
+        newPgrp:false
+        inDirectory:nil
 
     "/ never reached ...
 
@@ -760,31 +760,31 @@
     "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.
+         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.
+        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.
+        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.
+        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.
+        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
@@ -792,28 +792,28 @@
      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."
+            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
+        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'.
+        'I am the child'.
+        OperatingSystem exec:'/bin/ls' withArguments:#('ls' '/tmp').
+        'not reached'.
      ]
     "
     "
@@ -821,11 +821,11 @@
 
      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'.
+        '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.
@@ -849,57 +849,57 @@
 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.
+         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.
+        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.
+        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.
+        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.
+        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."
+            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
+        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'.
+        'I am the child'.
+        OperatingSystem exec:'/bin/ls' withArguments:#('ls' '/tmp').
+        'not reached'.
      ]
     "
     "
@@ -907,11 +907,11 @@
 
      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'.
+        '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.
@@ -929,14 +929,14 @@
      Not needed with Unix"
 
     ^ self
-	exec:aCommandPath 
-	withArguments:argArray 
-	environment:nil
-	fileDescriptors:fdArray
-	closeDescriptors:closeFdArray 
-	fork:doFork 
-	newPgrp:newPgrp
-	inDirectory:aDirectory
+        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"
@@ -949,26 +949,26 @@
      (typically, the xterm window)"
 
     ^ self 
-	exec:aCommandPath 
-	withArguments:argArray 
-	environment:nil
-	fileDescriptors:nil
-	closeDescriptors:nil 
-	fork:doFork 
-	newPgrp:false
-	inDirectory:nil
+        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'.
+        'I am the child'.
+        OperatingSystem 
+            exec:'/bin/ls' 
+            withArguments:#('ls' '/tmp')
+            fork:false.
+        'not reached'.
      ]
     "
 
@@ -977,12 +977,12 @@
 
      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'.
+        '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.
@@ -1002,26 +1002,26 @@
      (typically, the xterm window)"
 
     ^ self 
-	exec:aCommandPath
-	withArguments:argArray
-	environment:nil
-	fileDescriptors:nil
-	closeDescriptors:nil
-	fork:doFork 
-	newPgrp:false
-	inDirectory:aDirectory
+        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'.
+        'I am the child'.
+        OperatingSystem 
+            exec:'/bin/ls' 
+            withArguments:#('ls' '/tmp')
+            fork:false.
+        'not reached'.
      ]
     "
 
@@ -1030,12 +1030,12 @@
 
      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'.
+        '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.
@@ -1065,12 +1065,12 @@
      Return true if successful, false otherwise."
 
      ^ self
-	executeCommand:aCommandString 
-	inputFrom:nil 
-	outputTo:nil 
-	errorTo:nil 
-	inDirectory:nil
-	onError:[:status| false]
+        executeCommand:aCommandString 
+        inputFrom:nil 
+        outputTo:nil 
+        errorTo:nil 
+        inDirectory:nil
+        onError:[:status| false]
 
     "unix:
 
@@ -1104,9 +1104,9 @@
      hardwiring any 'cd ..' command strings into your applictions."
 
      ^ self
-	executeCommand:aCommandString
-	inDirectory:aDirectory
-	onError:[:status| false]
+        executeCommand:aCommandString
+        inDirectory:aDirectory
+        onError:[:status| false]
 
     "
      OperatingSystem executeCommand:'tdump date.obj' inDirectory:'c:\winstx\stx\libbasic\objbc'. 
@@ -1129,12 +1129,12 @@
      (containing the exit status) as argument."
 
     ^ self
-	executeCommand:aCommandString 
-	inputFrom:nil 
-	outputTo:nil 
-	errorTo:nil 
-	inDirectory:aDirectory
-	onError:aBlock
+        executeCommand:aCommandString 
+        inputFrom:nil 
+        outputTo:nil 
+        errorTo:nil 
+        inDirectory:aDirectory
+        onError:aBlock
 
     "Modified: / 10.11.1998 / 20:54:37 / cg"
 !
@@ -1160,114 +1160,111 @@
     terminateLock := Semaphore forMutualExclusion.
     ((externalInStream := anInStream) notNil 
      and:[externalInStream isExternalStream not]) ifTrue:[
-	pIn := ExternalStream makePipe.
-	inStreamToClose := externalInStream := pIn at:1.
-
-	"/ start a reader process, shuffling data from the given
-	"/ inStream to the pipe (which is connected to the commands input)
-	inputShufflerProcess := [
-		    |s|
-
-		    s := pIn at:2.   "/ thats where the shuffler writes to
-		    [
-			[s atEnd] whileFalse:[
-			    self 
-				shuffleFrom:anInStream
-				to:s
-				lineWise:lineWise.
-			    s flush
-			]
-		    ] ensure:[
-			s close
-		    ]
-		] forkNamed:'cmd input shuffler'.
+        pIn := ExternalStream makePipe.
+        inStreamToClose := externalInStream := pIn at:1.
+
+        "/ start a reader process, shuffling data from the given
+        "/ inStream to the pipe (which is connected to the commands input)
+        inputShufflerProcess := [
+                    |s|
+
+                    s := pIn at:2.   "/ thats where the shuffler writes to
+                    [
+                        [s atEnd] whileFalse:[
+                            self shuffleFrom:anInStream to:s lineWise:lineWise.
+                            s flush
+                        ]
+                    ] ensure:[
+                        s close
+                    ]
+                ] forkNamed:'cmd input shuffler'.
     ].
     ((externalOutStream := anOutStream) notNil 
      and:[externalOutStream isExternalStream not]) ifTrue:[
-	pOut := ExternalStream makePipe.
-	outStreamToClose := externalOutStream := pOut at:2.
-	outputShufflerProcess := 
-		    [
-			self shuffleAllFrom:(pOut at:1) to:anOutStream lineWise:lineWise lockWith:terminateLock.    
-		    ] forkNamed:'cmd output shuffler'.
+        pOut := ExternalStream makePipe.
+        outStreamToClose := externalOutStream := pOut at:2.
+        outputShufflerProcess := 
+                    [
+                        self shuffleAllFrom:(pOut at:1) to:anOutStream lineWise:lineWise lockWith:terminateLock.    
+                    ] forkNamed:'cmd output shuffler'.
     ].
     (externalErrStream := anErrStream) notNil ifTrue:[
-	anErrStream == anOutStream ifTrue:[
-	    externalErrStream := externalOutStream
-	] ifFalse:[
-	    anErrStream isExternalStream ifFalse:[
-		pErr := ExternalStream makePipe.
-		errStreamToClose := externalErrStream := pErr at:2.
-		errorShufflerProcess := 
-			[
-			    self shuffleAllFrom:(pErr at:1) to:anErrStream lineWise:lineWise lockWith:terminateLock.    
-			] forkNamed:'cmd err-output shuffler'.
-	    ]
-	]
+        anErrStream == anOutStream ifTrue:[
+            externalErrStream := externalOutStream
+        ] ifFalse:[
+            anErrStream isExternalStream ifFalse:[
+                pErr := ExternalStream makePipe.
+                errStreamToClose := externalErrStream := pErr at:2.
+                errorShufflerProcess := 
+                        [
+                            self shuffleAllFrom:(pErr at:1) to:anErrStream lineWise:lineWise lockWith:terminateLock.    
+                        ] forkNamed:'cmd err-output shuffler'.
+            ]
+        ]
     ].
     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
-		    ]
-		].
+                monitor:[
+                    self 
+                        startProcess:aCommandString
+                        inputFrom:externalInStream
+                        outputTo:externalOutStream
+                        errorTo:externalErrStream
+                        inDirectory:dirOrNil
+                ]
+                action:[:status | 
+                    status stillAlive ifFalse:[
+                        exitStatus := status.
+                        sema signal.
+                        self closePid:pid
+                    ]
+                ].
 
     inStreamToClose notNil ifTrue:[
-	inStreamToClose close
+        inStreamToClose close
     ].
     errStreamToClose notNil ifTrue:[
-	errStreamToClose close
+        errStreamToClose close
     ].
     outStreamToClose notNil ifTrue:[
-	outStreamToClose close
+        outStreamToClose close
     ].
 
     stopShufflers := [
-	    inputShufflerProcess notNil ifTrue:[
-		terminateLock critical:[inputShufflerProcess terminate].
-		inputShufflerProcess waitUntilTerminated
-	    ].
-	    outputShufflerProcess notNil ifTrue:[
-		terminateLock critical:[outputShufflerProcess terminate].
-		outputShufflerProcess waitUntilTerminated.
-		self shuffleRestFrom:(pOut at:1) to:anOutStream lineWise:lineWise.
-		(pOut at:1) close.
-	    ].
-	    errorShufflerProcess notNil ifTrue:[
-		terminateLock critical:[errorShufflerProcess terminate].
-		errorShufflerProcess waitUntilTerminated.
-		self shuffleRestFrom:(pErr at:1) to:anErrStream lineWise:lineWise.
-		(pErr at:1) close.
-	    ].
-	].
+            inputShufflerProcess notNil ifTrue:[
+                terminateLock critical:[inputShufflerProcess terminate].
+                inputShufflerProcess waitUntilTerminated
+            ].
+            outputShufflerProcess notNil ifTrue:[
+                terminateLock critical:[outputShufflerProcess terminate].
+                outputShufflerProcess waitUntilTerminated.
+                self shuffleRestFrom:(pOut at:1) to:anOutStream lineWise:lineWise.
+                (pOut at:1) close.
+            ].
+            errorShufflerProcess notNil ifTrue:[
+                terminateLock critical:[errorShufflerProcess terminate].
+                errorShufflerProcess waitUntilTerminated.
+                self shuffleRestFrom:(pErr at:1) to:anErrStream lineWise:lineWise.
+                (pErr at:1) close.
+            ].
+        ].
 
     pid notNil ifTrue:[
-	[
-	    sema wait.
-	] ifCurtailed:[
-	    "/ terminate the os-command (and all of its forked commands)
-	    self terminateProcessGroup:pid.
-	    self terminateProcess:pid.
-	    self closePid:pid.
-	    stopShufflers value.    
-	]
+        [
+            sema wait.
+        ] ifCurtailed:[
+            "/ terminate the os-command (and all of its forked commands)
+            self terminateProcessGroup:pid.
+            self terminateProcess:pid.
+            self closePid:pid.
+            stopShufflers value.    
+        ]
     ] ifFalse:[
-	exitStatus := self osProcessStatusClass processCreationFailure
+        exitStatus := self osProcessStatusClass processCreationFailure
     ].
     stopShufflers value.
     exitStatus success ifFalse:[
-	^ aBlock value:exitStatus
+        ^ aBlock value:exitStatus
     ].
     ^ true
 !
@@ -1287,43 +1284,43 @@
      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
+        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]
+         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]
+         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].
+         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].
+         executeCommand:'sh foo'
+         inputFrom:nil
+         outputTo:s
+         errorTo:s
+         onError:[:status | Transcript flash].
      Transcript showCR:s contents.
     "
 
@@ -1342,55 +1339,55 @@
      (containing the exit status) as argument."
 
     ^ self
-	executeCommand:aCommandString 
-	inputFrom:anInStream 
-	outputTo:anOutStream 
-	errorTo:anErrStream 
-	inDirectory:nil
-	onError:aBlock
+        executeCommand:aCommandString 
+        inputFrom:anInStream 
+        outputTo:anOutStream 
+        errorTo:anErrStream 
+        inDirectory:nil
+        onError:aBlock
 
     "
-	OperatingSystem
-	    executeCommand:'dir'                              
-	    inputFrom:nil
-	    outputTo:nil
-	    errorTo:nil
-	    onError:[:status | Transcript flash]
+        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]
+        OperatingSystem
+            executeCommand:'foo'
+            inputFrom:nil
+            outputTo:nil
+            errorTo:nil
+            onError:[:status | Transcript flash]
     "
     "
-	|outStr errStr|
-
-	outStr := '' writeStream.
-	errStr := '' writeStream.
-	OperatingSystem
-	    executeCommand:'ls'
-	    inputFrom:nil
-	    outputTo:outStr
-	    errorTo:errStr
-	    onError:[:status | Transcript flash].
-	Transcript show:'out:'; showCR:outStr contents.
-	Transcript show:'err:'; showCR:errStr contents.
+        |outStr errStr|
+
+        outStr := '' writeStream.
+        errStr := '' writeStream.
+        OperatingSystem
+            executeCommand:'ls'
+            inputFrom:nil
+            outputTo:outStr
+            errorTo:errStr
+            onError:[:status | Transcript flash].
+        Transcript show:'out:'; showCR:outStr contents.
+        Transcript show:'err:'; showCR:errStr contents.
     "
     "
-	|outStr errStr|
-
-	outStr := '' writeStream.
-	errStr := '' writeStream.
-	OperatingSystem
-	    executeCommand:'ls /fooBar'
-	    inputFrom:nil
-	    outputTo:outStr
-	    errorTo:errStr
-	    onError:[:status | Transcript flash].
-	Transcript show:'out:'; showCR:outStr contents.
-	Transcript show:'err:'; showCR:errStr contents.
+        |outStr errStr|
+
+        outStr := '' writeStream.
+        errStr := '' writeStream.
+        OperatingSystem
+            executeCommand:'ls /fooBar'
+            inputFrom:nil
+            outputTo:outStr
+            errorTo:errStr
+            onError:[:status | Transcript flash].
+        Transcript show:'out:'; showCR:outStr contents.
+        Transcript show:'err:'; showCR:errStr contents.
     "
 
     "Modified: / 10.11.1998 / 20:51:39 / cg"
@@ -1405,12 +1402,12 @@
      (containing the exit status) as argument."
 
     ^ self
-	executeCommand:aCommandString 
-	inputFrom:nil 
-	outputTo:nil 
-	errorTo:nil 
-	inDirectory:nil
-	onError:aBlock
+        executeCommand:aCommandString 
+        inputFrom:nil 
+        outputTo:nil 
+        errorTo:nil 
+        inDirectory:nil
+        onError:aBlock
 
     "unix:
 
@@ -1444,12 +1441,12 @@
     self obsoleteMethodWarning:'use executeCommand:inDirectory:onError:'.
 
     ^ self
-	executeCommand:aCommandString 
-	inputFrom:nil 
-	outputTo:nil 
-	errorTo:nil 
-	inDirectory:aDirectory
-	onError:aBlock
+        executeCommand:aCommandString 
+        inputFrom:nil 
+        outputTo:nil 
+        errorTo:nil 
+        inDirectory:aDirectory
+        onError:aBlock
 
     "Modified: / 10.11.1998 / 20:54:37 / cg"
 !
@@ -1460,12 +1457,12 @@
      hardwiring any 'cd ..' command strings into your applictions."
 
      ^ self
-	executeCommand:aCommandString
-	inputFrom:nil
-	outputTo:outStreamOrNil
-	errorTo:errStreamOrNil
-	inDirectory:aDirectory
-	onError:[:status| false]
+        executeCommand:aCommandString
+        inputFrom:nil
+        outputTo:outStreamOrNil
+        errorTo:errStreamOrNil
+        inDirectory:aDirectory
+        onError:[:status| false]
 
     "
      OperatingSystem executeCommand:'tdump date.obj' inDirectory:'c:\winstx\stx\libbasic\objbc'. 
@@ -1508,7 +1505,7 @@
 
     result := self getCommandOutputFrom:aCommand maxNumberOfLines:1 errorDisposition:#discard.
     result notNil ifTrue:[
-	^ result firstIfEmpty:['']
+        ^ result firstIfEmpty:['']
     ].
     ^ result
 
@@ -1539,34 +1536,34 @@
     |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
-		    ]
-		].
-	    ].
-	].
+        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
 
@@ -1654,11 +1651,11 @@
      or #killProcess: to stop it."
 
     ^ self
-	startProcess:aCommandString 
-	inputFrom:nil 
-	outputTo:nil 
-	errorTo:nil 
-	inDirectory:nil
+        startProcess:aCommandString 
+        inputFrom:nil 
+        outputTo:nil 
+        errorTo:nil 
+        inDirectory:nil
 
     "
      |pid|
@@ -1678,11 +1675,11 @@
      |pid|
 
      pid := OperatingSystem 
-		startProcess:'dir/l'
-		inputFrom:nil
-		outputTo:Stdout
-		errorTo:nil
-		inDirectory:nil.
+                startProcess:'dir/l'
+                inputFrom:nil
+                outputTo:Stdout
+                errorTo:nil
+                inDirectory:nil.
      (Delay forSeconds:2) wait.
      OperatingSystem killProcess:pid.
     "
@@ -1701,11 +1698,11 @@
      or #killProcess: to stop it."
 
     ^ self
-	startProcess:aCommandString 
-	inputFrom:nil 
-	outputTo:nil 
-	errorTo:nil 
-	inDirectory:aDirectory
+        startProcess:aCommandString 
+        inputFrom:nil 
+        outputTo:nil 
+        errorTo:nil 
+        inDirectory:aDirectory
     "
      |pid|
 
@@ -1731,11 +1728,11 @@
      or #killProcess: to stop it."
 
      ^ self     
-	startProcess:aCommandString 
-	inputFrom:anExternalInStream 
-	outputTo:anExternalOutStream 
-	errorTo:anExternalErrStream 
-	inDirectory:nil
+        startProcess:aCommandString 
+        inputFrom:anExternalInStream 
+        outputTo:anExternalOutStream 
+        errorTo:anExternalErrStream 
+        inDirectory:nil
 
     "Modified: / 10.11.1998 / 20:59:05 / cg"
 !
@@ -1829,13 +1826,13 @@
     "open a file, return an os specific fileHandle. 
      openmode is a symbol defining the way to open
      valid modes are:
-	#read
-	#write  
-	#readWrite
-	#appendWrite
-	#appendReadWrite
-	#createWrite
-	#createReadWrite
+        #read
+        #write  
+        #readWrite
+        #appendWrite
+        #appendReadWrite
+        #createWrite
+        #createReadWrite
 
      attributeSpec is an additional argument, currently only used with VMS
      - it allows a file to be created as fixedRecord, variableRecord, streamLF, streamCR, ...
@@ -1878,10 +1875,10 @@
      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:"
+        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
 
@@ -1901,8 +1898,8 @@
 
     self createDirectory:dirName.
     (self isDirectory:dirName) ifFalse:[
-	(self recursiveCreateDirectory:(dirName asFilename directoryName)) ifFalse:[^ false].
-	^ self createDirectory:dirName
+        (self recursiveCreateDirectory:(dirName asFilename directoryName)) ifFalse:[^ false].
+        ^ self createDirectory:dirName
     ].
     ^ true
 
@@ -1920,10 +1917,10 @@
      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:"
+        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
 
@@ -1991,7 +1988,7 @@
 
     "
      this could have been implemented as:
-	(self infoOf:aPathName) at:#mode
+        (self infoOf:aPathName) at:#mode
      but for huge directory searches the code below is faster
     "
 
@@ -2144,8 +2141,8 @@
      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
+        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.
@@ -2173,9 +2170,9 @@
     "/ root, home and current directories.
     "/
     ^ Array 
-	with:'/'
-	with:(self getHomeDirectory)
-	with:(Filename currentDirectory pathName)
+        with:'/'
+        with:(self getHomeDirectory)
+        with:(Filename currentDirectory pathName)
 
     "Modified: / 5.5.1999 / 01:06:26 / cg"
 !
@@ -2185,8 +2182,8 @@
      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
+        mountPoint - mount point
+        fileSystem - device or NFS-remotePath
     "
 
     ^ #()
@@ -2233,16 +2230,16 @@
     "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)
+         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.
@@ -2511,8 +2508,8 @@
 disableTimer
     "disable timer interrupts.
      WARNING: 
-	the system will not operate correctly with timer interrupts
-	disabled, because no scheduling or timeouts are possible."
+        the system will not operate correctly with timer interrupts
+        disabled, because no scheduling or timeouts are possible."
 
     self subclassResponsibility
 !
@@ -2521,9 +2518,9 @@
     "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."
+         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).
@@ -2661,8 +2658,8 @@
      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."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self subclassResponsibility
 
@@ -2674,8 +2671,8 @@
      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."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self subclassResponsibility
 
@@ -2725,7 +2722,7 @@
     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" 
+             therefore, keep SIGIO always above the two below" 
     aSignalNumber == self sigPOLL   ifTrue:[^ 'io available'].
     aSignalNumber == self sigURG    ifTrue:[^ 'urgent'].
 
@@ -2742,7 +2739,7 @@
      operatingSystem-signal occurs, or nil"
 
     OSSignals notNil ifTrue:[
-	^ OSSignals at:signalNumber ifAbsent:[nil]
+        ^ OSSignals at:signalNumber ifAbsent:[nil]
     ].
     ^ nil
 !
@@ -2751,7 +2748,7 @@
     "install a signal to be raised when an operatingSystem-signal occurs"
 
     OSSignals isNil ifTrue:[
-	OSSignals := Array new:32
+        OSSignals := Array new:32
     ].
     OSSignals at:signalNumber put:aSignal
 !
@@ -2763,9 +2760,9 @@
      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."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId
+              if the signal terminates that process."
 
     self subclassResponsibility
 !
@@ -2777,7 +2774,7 @@
      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."
+               spy interrupts."
 
     ^ false
 !
@@ -2785,7 +2782,7 @@
 stopSpyTimer
     "stop spy timing - disable spy timer.
      OBSOLETE: the new messageTally runs as a high prio process, not using 
-	       spy interrupts."
+               spy interrupts."
 
     ^ false
 !
@@ -2795,8 +2792,8 @@
      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."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self subclassResponsibility
 !
@@ -2806,8 +2803,8 @@
      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."
+              you may have to fetch the processes exitstatus with
+              OperatingSystem>>getStatusOfProcess:aProcessId."
 
     self subclassResponsibility
 !
@@ -2849,7 +2846,7 @@
     int code = 1;
 
     if (__isSmallInteger(exitCode)) {
-	code = __intVal(exitCode);
+        code = __intVal(exitCode);
     }
     __mainExit(code);
 %}
@@ -3003,7 +3000,7 @@
 getDomainName
     "return the domain this host is in.
      Notice:
-	not all systems support this; on some, 'unknown' is returned."
+        not all systems support this; on some, 'unknown' is returned."
 
     self subclassResponsibility
 !
@@ -3018,7 +3015,7 @@
     "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."
+        not all systems support this; on some, 'unknown' is returned."
 
     self subclassResponsibility
 !
@@ -3027,42 +3024,42 @@
     "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>
+        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.
 
@@ -3264,7 +3261,7 @@
     "if supported by the OS, return the systemID;
      a unique per machine identification.
      WARNING:
-	not all systems support this; on some, 'unknown' is returned."
+        not all systems support this; on some, 'unknown' is returned."
 
     ^ 'unknown'
 
@@ -3286,16 +3283,16 @@
        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).
+        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 ...)
+        #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|
@@ -3422,11 +3419,11 @@
 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."
+         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
 !
@@ -3634,24 +3631,24 @@
     "/
     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
-	    ]
-	].
+        (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
+            ]
+        ].
     ].                                                              
 
     "/
@@ -3659,21 +3656,21 @@
     "/
     p := OperatingSystem getEnvironment:'STX_TOPDIR'.
     p notNil ifTrue:[
-	(pPath includes:p) ifFalse:[
-	    pPath add:p
-	].
+        (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.
-	    ].
-	].
+        p := p asCollectionOfSubstringsSeparatedBy:$:.
+        p reverseDo:[:dir|
+            (pPath includes:dir) ifFalse:[
+                pPath addFirst:dir.
+            ].
+        ].
     ].
 
     ^ pPath
@@ -3714,20 +3711,20 @@
 "/            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
-	    ]
-	].
+        "/
+        "/ 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
+            ]
+        ].
     ].
 
     "/
@@ -3735,14 +3732,14 @@
     "/
     #( 'SMALLTALK_LIBDIR'
        'STX_LIBDIR'
-	'STX_TOPDIR'
+        'STX_TOPDIR'
      ) do:[:each |
-	p := OperatingSystem getEnvironment:each.
-	p notNil ifTrue:[
-	    (sysPath includes:p) ifFalse:[
-		sysPath add:p
-	    ]
-	].
+        p := OperatingSystem getEnvironment:each.
+        p notNil ifTrue:[
+            (sysPath includes:p) ifFalse:[
+                sysPath add:p
+            ]
+        ].
     ].
     ^ sysPath
 
@@ -3761,14 +3758,14 @@
 
 shuffleAllFrom:anInStream to:anOutStream lineWise:lineWise lockWith:aLock
     [anInStream atEnd] whileFalse:[
-	anInStream readWait.
-	aLock
-	    critical:[
-		self 
-		    shuffleFrom:anInStream
-		    to:anOutStream
-		    lineWise:lineWise
-	    ]
+        anInStream readWait.
+        aLock
+            critical:[
+                self 
+                    shuffleFrom:anInStream
+                    to:anOutStream
+                    lineWise:lineWise
+            ]
     ]
 !
 
@@ -3776,27 +3773,28 @@
     |data nShuffled|
 
     lineWise ifTrue:[
-	data := anInStream nextLine.
-	nShuffled := data size.
-	nShuffled > 0 ifTrue:[
-	    anOutStream nextPutLine:data
-	]
+        anInStream readWait.
+        data := anInStream nextLine.
+        nShuffled := data size.
+        nShuffled > 0 ifTrue:[
+            anOutStream nextPutLine:data
+        ]
     ] ifFalse:[
-	data := anInStream nextAvailable:1024.
-	nShuffled := data size.
-	nShuffled > 0 ifTrue:[
-	    anOutStream nextPutAll:data
-	]
+        data := anInStream nextAvailable:1024.
+        nShuffled := data size.
+        nShuffled > 0 ifTrue:[
+            anOutStream nextPutAll:data
+        ]
     ].
     ^ nShuffled
 !
 
 shuffleRestFrom:anInStream to:anOutStream lineWise:lineWise 
     [
-	self 
-	    shuffleFrom:anInStream
-	    to:anOutStream
-	    lineWise:lineWise.
+        self 
+            shuffleFrom:anInStream
+            to:anOutStream
+            lineWise:lineWise.
     ] doUntil:[anInStream atEnd].
 ! !
 
@@ -3916,8 +3914,8 @@
      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.
+        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.
@@ -3966,9 +3964,9 @@
     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.
+        delta := self millisecondTimeDeltaBetween:then and:now.
+        self selectOnAnyReadable:nil writable:nil exception:nil withTimeOut:delta.
+        now := self getMillisecondTime.
     ]
 
     "
@@ -3984,13 +3982,13 @@
      This should really be moved to some RelativeTime class."
 
     (msTime1 > msTime2) ifTrue:[
-	((msTime1 - msTime2) >= 16r10000000) ifTrue:[
-	    ^ false
-	].
-	^ true
+        ((msTime1 - msTime2) >= 16r10000000) ifTrue:[
+            ^ false
+        ].
+        ^ true
     ].
     ((msTime2 - msTime1) > 16r10000000) ifTrue:[
-	^ true
+        ^ true
     ].
     ^ false
 !
@@ -4020,7 +4018,7 @@
      better yet: create a subclass of Integer named LimitedRangeInteger."
 
     (msTime1 > msTime2) ifTrue:[
-	^ msTime1 - msTime2
+        ^ msTime1 - msTime2
     ].
     ^ msTime1 + 16r10000000 - msTime2
 
@@ -4200,7 +4198,7 @@
     "/ fallBack dummy
 
     aNumber == self getUserID ifTrue:[
-	^ self getLoginName
+        ^ self getLoginName
     ].
 
     ^ '? (' , aNumber printString , ')'
@@ -4279,20 +4277,20 @@
      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
+        "/ 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].
+                     writable:nil
+                    exception:nil
+                  withTimeOut:0) == fd
+        ifTrue:[^ true].
     ^ false
 !
 
@@ -4302,19 +4300,19 @@
      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
+        "/ 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].
+                     writable:(Array with:fd)
+                    exception:nil
+                  withTimeOut:0) == fd
+        ifTrue:[^ true].
     ^ false
 !
 
@@ -4323,12 +4321,12 @@
      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."
+        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
+                      writable:(Array with:fd1 with:fd2)
+                     exception:nil
+                   withTimeOut:millis
 !
 
 selectOn:fd withTimeOut:millis
@@ -4339,9 +4337,9 @@
      Experimental."
 
     ^ self selectOnAnyReadable:(Array with:fd)
-		      writable:(Array with:fd)
-		     exception:nil
-		   withTimeOut:millis
+                      writable:(Array with:fd)
+                     exception:nil
+                   withTimeOut:millis
 !
 
 selectOnAny:fdArray withTimeOut:millis
@@ -4351,9 +4349,9 @@
      Experimental."
 
     ^ self selectOnAnyReadable:fdArray
-		      writable:fdArray
-		     exception:nil
-		   withTimeOut:millis
+                      writable:fdArray
+                     exception:nil
+                   withTimeOut:millis
 !
 
 selectOnAnyReadable:fdArray withTimeOut:millis
@@ -4364,9 +4362,9 @@
      Experimental."
 
     ^ self selectOnAnyReadable:fdArray 
-		      writable:nil 
-		     exception:nil
-		   withTimeOut:millis
+                      writable:nil 
+                     exception:nil
+                   withTimeOut:millis
 !
 
 selectOnAnyReadable:readFdArray writable:writeFdArray exception:exceptFdArray withTimeOut:millis
@@ -4396,25 +4394,25 @@
     "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
+        "/ 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].
+                     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.72 2002-07-22 15:08:10 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.73 2002-08-02 14:22:33 penk Exp $'
 ! !
 AbstractOperatingSystem initialize!