AbstractOperatingSystem.st
changeset 17362 c07512e3643c
parent 17178 623ad6fc9dca
child 17431 bab67ea3bf22
--- a/AbstractOperatingSystem.st	Mon Feb 02 17:18:04 2015 +0100
+++ b/AbstractOperatingSystem.st	Mon Feb 02 17:26:18 2015 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#AbstractOperatingSystem
 	instanceVariableNames:''
 	classVariableNames:'ConcreteClass LastErrorNumber LocaleInfo OSSignals PipeFailed
@@ -1313,241 +1315,255 @@
 
      Set lineWise to true, if both error and output is sent to the same stream
      and you don't want lines to be mangled. Set lineWise = false to
-     avoid vlocking on pipes"
+     avoid blocking on pipes"
 
     |pid exitStatus sema pIn pOut pErr pAux externalInStream externalOutStream externalErrStream externalAuxStream
      shuffledInStream shuffledOutStream shuffledErrStream shuffledAuxStream
      inputShufflerProcess outputShufflerProcess errorShufflerProcess auxShufflerProcess stopShufflers
-     inStreamToClose outStreamToClose errStreamToClose auxStreamToClose terminateLock
+     inStreamToClose outStreamToClose errStreamToClose auxStreamToClose nullStream terminateLock
      closeStreams|
 
     terminateLock := Semaphore forMutualExclusion.
     ((externalInStream := anInStream) notNil
      and:[externalInStream isExternalStream not]) ifTrue:[
-	pIn := NonPositionableExternalStream makePipe.
-	inStreamToClose := externalInStream := pIn at:1.
-	shuffledInStream := pIn at:2.
-	anInStream isBinary ifTrue:[
-	    shuffledInStream binary
-	].
-	lineWise ifFalse:[
-	    shuffledInStream blocking:false.
-	].
-
-	"/ start a reader process, shuffling data from the given
-	"/ inStream to the pipe (which is connected to the commands input)
-	inputShufflerProcess :=
-	    [
-		[
-		    [anInStream atEnd] whileFalse:[
-			self shuffleFrom:anInStream to:shuffledInStream lineWise:lineWise.
-			shuffledInStream flush
-		    ]
-		] ensure:[
-		    shuffledInStream close
-		]
-	    ] newProcess
-		name:'cmd input shuffler';
+        pIn := NonPositionableExternalStream makePipe.
+        inStreamToClose := externalInStream := pIn at:1.
+        shuffledInStream := pIn at:2.
+        anInStream isBinary ifTrue:[
+            shuffledInStream binary
+        ].
+        lineWise ifFalse:[
+            shuffledInStream blocking:false.
+        ].
+
+        "/ start a reader process, shuffling data from the given
+        "/ inStream to the pipe (which is connected to the commands input)
+        inputShufflerProcess :=
+            [
+                [
+                    [anInStream atEnd] whileFalse:[
+                        self shuffleFrom:anInStream to:shuffledInStream lineWise:lineWise.
+                        shuffledInStream flush
+                    ]
+                ] ensure:[
+                    shuffledInStream close
+                ]
+            ] newProcess
+                name:'cmd input shuffler';
 "/                beSystemProcess;
-		resume.
+                resume.
     ].
     ((externalOutStream := anOutStream) notNil
      and:[externalOutStream isExternalStream not]) ifTrue:[
-	pOut := NonPositionableExternalStream makePipe.
-	shuffledOutStream := (pOut at:1).
-	anOutStream isBinary ifTrue:[
-	    shuffledOutStream binary
-	].
-	outStreamToClose := externalOutStream := pOut at:2.
-	outputShufflerProcess :=
-	    [
-		WriteError handle:[:ex |
-		    "/ ignored
-		] do:[
-		    self shuffleAllFrom:shuffledOutStream to:anOutStream lineWise:lineWise lockWith:terminateLock.
-		].
-	    ] newProcess
-		priority:(Processor userSchedulingPriority + 1);
-		name:'cmd output shuffler';
+        pOut := NonPositionableExternalStream makePipe.
+        shuffledOutStream := (pOut at:1).
+        anOutStream isBinary ifTrue:[
+            shuffledOutStream binary
+        ].
+        outStreamToClose := externalOutStream := pOut at:2.
+        outputShufflerProcess :=
+            [
+                WriteError handle:[:ex |
+                    "/ ignored
+                ] do:[
+                    self shuffleAllFrom:shuffledOutStream to:anOutStream lineWise:lineWise lockWith:terminateLock.
+                ].
+            ] newProcess
+                priority:(Processor userSchedulingPriority + 1);
+                name:'cmd output shuffler';
 "/                beSystemProcess;
-		resume.
+                resume.
     ].
     (externalErrStream := anErrStream) notNil ifTrue:[
-	anErrStream == anOutStream ifTrue:[
-	    externalErrStream := externalOutStream
-	] ifFalse:[
-	    anErrStream isExternalStream ifFalse:[
-		pErr := NonPositionableExternalStream makePipe.
-		shuffledErrStream := (pErr at:1).
-		anErrStream isBinary ifTrue:[
-		    shuffledErrStream binary
-		].
-		errStreamToClose := externalErrStream := pErr at:2.
-		errorShufflerProcess :=
-		    [
-			self shuffleAllFrom:shuffledErrStream to:anErrStream lineWise:lineWise lockWith:terminateLock.
-		    ] newProcess
-			priority:(Processor userSchedulingPriority + 2);
-			name:'cmd err-output shuffler';
+        anErrStream == anOutStream ifTrue:[
+            externalErrStream := externalOutStream
+        ] ifFalse:[
+            anErrStream isExternalStream ifFalse:[
+                pErr := NonPositionableExternalStream makePipe.
+                shuffledErrStream := (pErr at:1).
+                anErrStream isBinary ifTrue:[
+                    shuffledErrStream binary
+                ].
+                errStreamToClose := externalErrStream := pErr at:2.
+                errorShufflerProcess :=
+                    [
+                        self shuffleAllFrom:shuffledErrStream to:anErrStream lineWise:lineWise lockWith:terminateLock.
+                    ] newProcess
+                        priority:(Processor userSchedulingPriority + 2);
+                        name:'cmd err-output shuffler';
 "/                        beSystemProcess;
-			resume.
-	    ]
-	]
+                        resume.
+            ]
+        ]
     ].
     ((externalAuxStream := anAuxStream) notNil
      and:[externalAuxStream isExternalStream not]) ifTrue:[
-	pAux := NonPositionableExternalStream makePipe.
-	auxStreamToClose := externalAuxStream := pAux at:1.
-	shuffledAuxStream := pAux at:2.
-	shuffledAuxStream blocking:false.
-	anAuxStream isBinary ifTrue:[
-	    shuffledAuxStream binary
-	].
-
-	"/ start a reader process, shuffling data from the given
-	"/ auxStream to the pipe (which is connected to the commands aux)
-	auxShufflerProcess :=
-	    [
-		[
-		    [anAuxStream atEnd] whileFalse:[
-			self shuffleFrom:anAuxStream to:shuffledAuxStream lineWise:false.
-			shuffledAuxStream flush
-		    ]
-		] ensure:[
-		    shuffledAuxStream close
-		]
-	    ] newProcess
-		name:'cmd aux shuffler';
+        pAux := NonPositionableExternalStream makePipe.
+        auxStreamToClose := externalAuxStream := pAux at:1.
+        shuffledAuxStream := pAux at:2.
+        shuffledAuxStream blocking:false.
+        anAuxStream isBinary ifTrue:[
+            shuffledAuxStream binary
+        ].
+
+        "/ start a reader process, shuffling data from the given
+        "/ auxStream to the pipe (which is connected to the commands aux)
+        auxShufflerProcess :=
+            [
+                [
+                    [anAuxStream atEnd] whileFalse:[
+                        self shuffleFrom:anAuxStream to:shuffledAuxStream lineWise:false.
+                        shuffledAuxStream flush
+                    ]
+                ] ensure:[
+                    shuffledAuxStream close
+                ]
+            ] newProcess
+                name:'cmd aux shuffler';
 "/                beSystemProcess;
-		resume.
+                resume.
     ].
 
     stopShufflers := [:shuffleRest |
-	inputShufflerProcess notNil ifTrue:[
-	    terminateLock critical:[inputShufflerProcess terminate].
-	    inputShufflerProcess waitUntilTerminated
-	].
-	auxShufflerProcess notNil ifTrue:[
-	    terminateLock critical:[auxShufflerProcess terminate].
-	    auxShufflerProcess waitUntilTerminated
-	].
-	outputShufflerProcess notNil ifTrue:[
-	    terminateLock critical:[outputShufflerProcess terminate].
-	    outputShufflerProcess waitUntilTerminated.
-	    shuffleRest ifTrue:[ self shuffleRestFrom:shuffledOutStream to:anOutStream lineWise:lineWise ].
-	    shuffledOutStream close.
-	].
-	errorShufflerProcess notNil ifTrue:[
-	    terminateLock critical:[errorShufflerProcess terminate].
-	    errorShufflerProcess waitUntilTerminated.
-	    shuffleRest ifTrue:[ self shuffleRestFrom:shuffledErrStream to:anErrStream lineWise:lineWise ].
-	    shuffledErrStream close.
-	].
-    ].
+            inputShufflerProcess notNil ifTrue:[
+                terminateLock critical:[inputShufflerProcess terminate].
+                inputShufflerProcess waitUntilTerminated
+            ].
+            auxShufflerProcess notNil ifTrue:[
+                terminateLock critical:[auxShufflerProcess terminate].
+                auxShufflerProcess waitUntilTerminated
+            ].
+            outputShufflerProcess notNil ifTrue:[
+                terminateLock critical:[outputShufflerProcess terminate].
+                outputShufflerProcess waitUntilTerminated.
+                shuffleRest ifTrue:[ self shuffleRestFrom:shuffledOutStream to:anOutStream lineWise:lineWise ].
+                shuffledOutStream close.
+            ].
+            errorShufflerProcess notNil ifTrue:[
+                terminateLock critical:[errorShufflerProcess terminate].
+                errorShufflerProcess waitUntilTerminated.
+                shuffleRest ifTrue:[ self shuffleRestFrom:shuffledErrStream to:anErrStream lineWise:lineWise ].
+                shuffledErrStream close.
+            ].
+        ].
 
     closeStreams := [
-	inStreamToClose notNil ifTrue:[
-	    inStreamToClose close
-	].
-	errStreamToClose notNil ifTrue:[
-	    errStreamToClose close
-	].
-	outStreamToClose notNil ifTrue:[
-	    outStreamToClose close
-	].
-	auxStreamToClose notNil ifTrue:[
-	    auxStreamToClose close
-	].
-    ].
+            inStreamToClose notNil ifTrue:[
+                inStreamToClose close
+            ].
+            errStreamToClose notNil ifTrue:[
+                errStreamToClose close
+            ].
+            outStreamToClose notNil ifTrue:[
+                outStreamToClose close
+            ].
+            auxStreamToClose notNil ifTrue:[
+                auxStreamToClose close
+            ].
+            nullStream notNil ifTrue:[
+                nullStream close
+            ].
+        ].
 
 
     sema := Semaphore new name:'OS command wait'.
     [
-	pid := Processor
-		    monitor:[
-			self
-			    startProcess:aCommandString
-			    inputFrom:externalInStream
-			    outputTo:externalOutStream
-			    errorTo:externalErrStream
-			    auxFrom:externalAuxStream
-			    environment:environmentDictionary
-			    inDirectory:dirOrNil
-		    ]
-		    action:[:status |
-			status stillAlive ifFalse:[
-			    exitStatus := status.
-			    sema signal.
-			    self closePid:pid
-			]
-		    ].
-
-	pid isNil ifTrue:[
-	    exitStatus := self osProcessStatusClass processCreationFailure
-	] ifFalse:[
-	    sema wait.
-	].
+        externalInStream isNil ifTrue:[
+            externalInStream := nullStream := Filename nullDevice readWriteStream.
+        ].
+        externalOutStream isNil ifTrue:[
+            nullStream isNil ifTrue:[nullStream := Filename nullDevice writeStream].
+            externalOutStream := nullStream.
+        ].
+        externalErrStream isNil ifTrue:[
+            externalErrStream := externalOutStream
+        ].
+
+        pid := Processor
+                    monitor:[
+                        self
+                            startProcess:aCommandString
+                            inputFrom:externalInStream
+                            outputTo:externalOutStream
+                            errorTo:externalErrStream
+                            auxFrom:externalAuxStream
+                            environment:environmentDictionary
+                            inDirectory:dirOrNil
+                    ]
+                    action:[:status |
+                        status stillAlive ifFalse:[
+                            exitStatus := status.
+                            sema signal.
+                            self closePid:pid
+                        ]
+                    ].
+
+        pid isNil ifTrue:[
+            exitStatus := self osProcessStatusClass processCreationFailure
+        ] ifFalse:[
+            sema wait.
+        ].
     ] ifCurtailed:[
-	closeStreams value.
-	pid notNil ifTrue:[
-	    "/ terminate the os-command (and all of its forked commands)
-	    self terminateProcessGroup:pid.
-	    self terminateProcess:pid.
-	    self closePid:pid.
-	].
-	stopShufflers value:false.
+        closeStreams value.
+        pid notNil ifTrue:[
+            "/ terminate the os-command (and all of its forked commands)
+            self terminateProcessGroup:pid.
+            self terminateProcess:pid.
+            self closePid:pid.
+        ].
+        stopShufflers value:false.
     ].
 
     closeStreams value.
     stopShufflers value:true.
     (exitStatus isNil or:[exitStatus success]) ifFalse:[
-	^ aBlock value:exitStatus
+        ^ aBlock value:exitStatus
     ].
     ^ true
 
     "
-	|outStream errStream|
-
-	outStream := '' writeStream.
-
-	OperatingSystem executeCommand:'ls -l'
-			inputFrom:'abc' readStream
-			outputTo:outStream
-			errorTo:nil
-			inDirectory:nil
-			lineWise:true
-			onError:[:exitStatus | ^ false].
-	outStream contents
-    "
-
-    "
-	|outStream errStream|
-
-	outStream := #[] writeStream.
-
-	OperatingSystem executeCommand:'cat'
-			inputFrom:(ByteArray new:5000000) readStream
-			outputTo:outStream
-			errorTo:nil
-			inDirectory:nil
-			lineWise:false
-			onError:[:exitStatus | ^ false].
-	outStream size
-    "
-
-    "
-	|outStream errStream|
-
-	outStream := '' writeStream.
-
-	OperatingSystem executeCommand:'gpg -s --batch --no-tty --passphrase-fd 0 /tmp/passwd'
-			inputFrom:'bla' readStream
-			outputTo:outStream
-			errorTo:nil
-			inDirectory:nil
-			lineWise:true
-			onError:[:exitStatus |  false].
-	outStream contents
+        |outStream errStream|
+
+        outStream := '' writeStream.
+
+        OperatingSystem executeCommand:'ls -l'
+                        inputFrom:'abc' readStream
+                        outputTo:outStream
+                        errorTo:nil
+                        inDirectory:nil
+                        lineWise:true
+                        onError:[:exitStatus | ^ false].
+        outStream contents
+    "
+
+    "
+        |outStream errStream|
+
+        outStream := #[] writeStream.
+
+        OperatingSystem executeCommand:'cat'
+                        inputFrom:(ByteArray new:5000000) readStream
+                        outputTo:outStream
+                        errorTo:nil
+                        inDirectory:nil
+                        lineWise:false
+                        onError:[:exitStatus | ^ false].
+        outStream size
+    "
+
+    "
+        |outStream errStream|
+
+        outStream := '' writeStream.
+
+        OperatingSystem executeCommand:'gpg -s --batch --no-tty --passphrase-fd 0 /tmp/passwd'
+                        inputFrom:'bla' readStream
+                        outputTo:outStream
+                        errorTo:nil
+                        inDirectory:nil
+                        lineWise:true
+                        onError:[:exitStatus |  false].
+        outStream contents
     "
 
     "Modified: / 11-02-2007 / 20:54:39 / cg"
@@ -7648,11 +7664,11 @@
 !AbstractOperatingSystem class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.287 2014-12-03 19:26:20 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.288 2015-02-02 16:26:18 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.287 2014-12-03 19:26:20 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.288 2015-02-02 16:26:18 stefan Exp $'
 ! !