AbstractOperatingSystem.st
changeset 4847 6d3b5959198f
parent 4377 59bb21ad2839
child 4848 035902e57400
--- a/AbstractOperatingSystem.st	Mon Oct 04 20:45:59 1999 +0200
+++ b/AbstractOperatingSystem.st	Wed Oct 06 13:28:09 1999 +0200
@@ -1084,59 +1084,196 @@
     "Created: / 10.11.1998 / 21:05:45 / cg"
 !
 
-executeCommand:aCommandString inputFrom:anExternalInStream outputTo:anExternalOutStream errorTo:anExternalErrStream inDirectory:dirOrNil onError:aBlock
+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."
-
-    |pid exitStatus sema|
+     (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|
+
+    (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:[
+                        data := anInStream nextAvailable:512.
+                        s nextPutAll:data.
+                        s flush.
+                    ]
+                ] valueNowOrOnUnwindDo:[
+                    (pIn at:1) close.
+                    (pIn at:2) close.
+                ]
+            ] newProcess.
+            inputShufflerProcess name:'cmd input shuffler'.
+            inputShufflerProcess resume.
+        ]   
+    ].
+
+    (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:[
+                        data := s nextAvailable:1024.
+                        anOutStream nextPutAll:data.
+                    ]
+                ] valueNowOrOnUnwindDo:[
+                    [
+                        data := s nextAvailable:1024.
+                        anOutStream nextPutAll:data.
+                    ] doUntil:[data size == 0].
+                    (pOut at:1) close.
+                    (pOut at:2) close.
+                ].
+            ] newProcess.
+            outputShufflerProcess name:'cmd output shuffler'.
+            outputShufflerProcess resume.
+        ]   
+    ].
+
+    (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:[
+                            data := s nextAvailable:512.
+                            anErrStream nextPutAll:data.
+                        ]
+                    ] valueNowOrOnUnwindDo:[
+                        [
+                            data := s nextAvailable:512.
+                            anErrStream nextPutAll:data.
+                        ] doUntil:[data size == 0].
+                        (pErr at:1) close.
+                        (pErr at:2) close.
+                    ]
+                ] newProcess.
+                errorShufflerProcess name:'cmd err-output shuffler'.
+                errorShufflerProcess resume.
+            ]   
+        ]   
+    ].
 
     sema := Semaphore new name:'OS command wait'.
 
     pid := Processor 
-		monitor:[
-		    self 
-			startProcess:aCommandString
-			inputFrom:anExternalInStream 
-			outputTo:anExternalOutStream 
-			errorTo:anExternalErrStream
-			inDirectory:dirOrNil.
-		] 
-		action:[:status |
-		    status stillAlive ifFalse:[
-			exitStatus := status.
-			self closePid:pid.
-			sema signal
-		    ].
-		].
+                monitor:[
+                    self 
+                        startProcess:aCommandString
+                        inputFrom:externalInStream 
+                        outputTo:externalOutStream 
+                        errorTo:externalErrStream
+                        inDirectory:dirOrNil.
+                ] 
+                action:[:status |
+                    status stillAlive ifFalse:[
+                        exitStatus := status.
+                        self closePid:pid.
+                        sema signal
+                    ].
+                ].
+
     pid notNil ifTrue:[
-	sema wait.
+        sema wait.
     ] ifFalse:[
-	exitStatus := self osProcessStatusClass processCreationFailure.
+        exitStatus := self osProcessStatusClass processCreationFailure.
+    ].
+
+    inputShufflerProcess notNil ifTrue:[
+        inputShufflerProcess terminate.
+        inputShufflerProcess waitUntilTerminated.
+    ].
+    outputShufflerProcess notNil ifTrue:[
+        Processor yield.
+        outputShufflerProcess terminate.
+        outputShufflerProcess waitUntilTerminated.
+    ].
+    errorShufflerProcess notNil ifTrue:[
+        Processor yield.
+        errorShufflerProcess terminate.
+        errorShufflerProcess waitUntilTerminated.
     ].
 
     exitStatus success ifFalse:[
-	^ aBlock value:exitStatus
+        ^ 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]
+     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"
@@ -3832,6 +3969,6 @@
 !AbstractOperatingSystem class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.24 1999-07-13 10:45:13 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.25 1999-10-06 11:28:09 cg Exp $'
 ! !
 AbstractOperatingSystem initialize!