OSProcess.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 20:55:17 +0200
changeset 24417 03b083548da2
parent 24290 36a25191f3e8
child 24429 d9f5afe53e2b
permissions -rw-r--r--
#REFACTORING by exept class: Smalltalk class changed: #recursiveInstallAutoloadedClassesFrom:rememberIn:maxLevels:noAutoload:packageTop:showSplashInLevels: Transcript showCR:(... bindWith:...) -> Transcript showCR:... with:...

"{ Encoding: utf8 }"

"{ Package: 'stx:libbasic' }"

"{ NameSpace: Smalltalk }"

Object subclass:#OSProcess
	instanceVariableNames:'pid command environment directory inStream outStream errorStream
		auxStream showWindow lineWise newPgrp exitStatus finishSema
		inputShufflerProcesses outputShufflerProcesses streamsToClose
		terminateActionBlock'
	classVariableNames:'Instances'
	poolDictionaries:''
	category:'System-Support'
!

Object subclass:#ProcessListEntry
	instanceVariableNames:'executableName processID sessionName userName'
	classVariableNames:''
	poolDictionaries:''
	privateIn:OSProcess
!

OSProcess subclass:#RemoteOSProcess
	instanceVariableNames:'host'
	classVariableNames:'MethodPerHost'
	poolDictionaries:''
	privateIn:OSProcess
!

!OSProcess class methodsFor:'documentation'!

documentation
"
    Instances of OSProcess represent operating system processes that can be executed.
    (as opposed to Smalltalk processes).
    Both local and remote processes are supported.

    commandString:
     If command is a String, the commandString is passed to a shell for execution
     - see the description of 'sh -c' in your UNIX manual ('cmd.exe' in your Windows manual).
     Regular input/output redirection and pipes etc. are supported as supported by
     the underlying OS's command interpreter (i.e. some limits apply to MSDOS)

     With an empty command, the shell will read commands from the passed input stream.

     If command is an Array, the first element is the command to be executed,
     and the other elements are the arguments to the command. 
     No shell is invoked in this case. Any redirection or piping can then be done
     by Smalltalk code (including piping through smalltalk streams & filters).

    [author:]
        Stefan Vogel (stefan@zwerg)

    [instance variables:]
        pid         SmallInteger    the process id
        command     String          the command line of the running command.

    [class variables:]

    [see also:]
        Process

"
!

examples
"
  send command's output to the Transcript:
                                                            [exBegin]
    OSProcess new 
        terminateActionBlock:[:status | Transcript showCR:status. Transcript showCR:status isError];
        command:'lsxxxx -l';
        outStream:Transcript;
        lineWise:true;
        startProcess.
                                                            [exEnd]

  send command's output to my stdout (see console):
                                                            [exBegin]
    OSProcess new 
        command:'ls -l';
        outStream:Stdout;
        execute.
                                                            [exEnd]

  send command's output to a Smalltalk stream:
                                                            [exBegin]
    |outStream|

    outStream := '' writeStream.

    OSProcess new 
        command:'ls -l';
        outStream:outStream;
        execute.

    outStream contents inspect.
                                                            [exEnd]

  feed it from a smalltalk stream, get command's output into a Smalltalk stream:
                                                            [exBegin]
    |inStream outStream|

    inStream := 'hello world' readStream.
    outStream := '' writeStream.

    OSProcess new 
        command:'tr ''a-z'' ''A-Z''';
        inStream:inStream;
        outStream:outStream;
        execute.

    outStream contents inspect.
                                                            [exEnd]

  again, send output to a Smalltalk stream;
  watch the stream getting filled after 10 seconds:
                                                            [exBegin]
    |outStream|

    outStream := '' writeStream.

    OSProcess new 
        command:'ls -l; sleep 10; echo =================================; echo hallo after 10s; echo >&2 +++++++++++++++++++++; cat >&2';
        outStream:outStream;
        errorStream:outStream;
        startProcess.

    outStream inspect
                                                            [exEnd]

  separate stdout and stderr:
                                                            [exBegin]
    |outStream errStream|

    outStream := '' writeStream.
    errStream := '' writeStream.

    OSProcess new 
        command:'ls -l && ls >&2';
        outStream:outStream;
        errorStream:errStream;
        startProcess.

    outStream inspect.
    errStream inspect.
                                                            [exEnd]

  Execute commands in shell/cmd.exe and read them from stdin:
                                                            [exBegin]
    |outStream|

    outStream := '' writeStream.

    OSProcess new 
        command:'';
        inStream:'ls -l' readStream;
        outStream:outStream;
        lineWise:true;
        execute.

    outStream contents inspect
                                                            [exEnd]

  Execute on a remote host (you must have the appropriate ssh setup):
                                                            [exBegin]
    |outStream|

    outStream := '' writeStream.

    (OSProcess onHost:'exeptn') 
        command:'ls -l';
        outStream:outStream;
        lineWise:true;
        execute.

    outStream contents inspect
                                                            [exEnd]
"
! !

!OSProcess class methodsFor:'instance creation'!

allInstancesDo:aBlock
    "return an initialized instance for a local process.
     Keep track of the new instance (so we can quickly enumerate all of them)"

    Instances notNil ifTrue:[ 
        Instances do:aBlock
    ].
    
    "
     super allInstances
     self allInstances
    "

    "Created: / 02-03-2019 / 19:19:41 / Claus Gittinger"
!

command:aCommandString
    "return an initialized instance to execute aCommandString
     in the current directory (for a local process)"

    ^ self new command:aCommandString.
!

command:aCommandString directory:aStringOrFilename
    "return an initialized instance to execute aCommandString 
     in a given directory (for a local process)"

    ^ self new command:aCommandString directory:aStringOrFilename.
!

commandStringForProgramName:executableFile arguments:arrayOfStrings
    "generate a command line string from appending args (possibley quoted) to the exe-name (with spaces)"

    ^ String streamContents:[:s |
        s nextPutAll:(self possiblyQuoted:executableFile asFilename pathName).
        arrayOfStrings notNil ifTrue:[
            arrayOfStrings do:[:eachArg |
                s space.
                s nextPutAll:(self possiblyQuoted:eachArg).
            ].
        ]
    ]

    "Modified (comment): / 02-07-2018 / 20:50:29 / cg"
!

new
    "return an initialized instance for a local process.
     Keep track of the new instance (so we can quickly enumerate all of them)"

    |newInst|
    
    Instances isNil ifTrue:[
        Instances := WeakIdentitySet new
    ].    
    newInst := self basicNew initialize.
    Instances add:newInst.
    ^ newInst

    "Modified (comment): / 02-03-2019 / 19:15:25 / Claus Gittinger"
!

onHost:aHost
    "return an initialized instance for a remote process running on another host"

    (SocketAddress hostName:aHost) isLocal ifTrue:[
        ^ self basicNew initialize.
    ].
    ^ RemoteOSProcess basicNew host:aHost; initialize.

    "
     OSProcess onHost:'localhost'
     OSProcess onHost:'exeptn'

     (OSProcess new) command:'ls'
     (OSProcess onHost:'exeptn') command:'ls'
    "
!

possiblyQuoted:aString
    "should we quote or escape?"

    "/ better quote - qorks on Windows AND Unix
    ^ Filename possiblyQuotedPathname:aString.

"/    ^ String streamContents:[:s |
"/        aString do:[:ch |
"/            (ch isSeparator or:[ch = $\]) ifTrue:[
"/                s nextPut:$\
"/            ].
"/            s nextPut:ch
"/        ]
"/    ]

    "
     self possiblyQuoted:'foo bar' 
     self possiblyQuoted:'foo\bar'
    "

    "Modified: / 28-03-2019 / 16:19:41 / Claus Gittinger"
!

programName:executableFile arguments:arrayOfStrings initialEnvironment:stringDictionary
    "similar to command:, but with separate command and arguments"

    ^ self new
        command:(self commandStringForProgramName:executableFile arguments:arrayOfStrings);
        environment:stringDictionary;
        yourself

    "
     (self programName:'notepad.exe' arguments:#() initialEnvironment:nil)
        showWindow:true;
        startProcess
    "

    "Modified (comment): / 02-07-2018 / 20:33:02 / cg"
! !

!OSProcess class methodsFor:'class initialization'!

initialize
    "Backward compatibility: Win32Process is an alias for OSProcess"

    Win32Process := self.
! !

!OSProcess class methodsFor:'queries'!

defaultShellPath
    OperatingSystem isUNIXlike ifTrue:[
        ^ OperatingSystem getEnvironment:'SHELL' 
    ].
    ^ 'cmd'
! !

!OSProcess class methodsFor:'utilities'!

getTaskList
    "get a tasklist (Windows OS only)"

    |lines sepIdx entries|

    OperatingSystem isMSWINDOWSlike ifTrue:[
        lines := (PipeStream outputFromCommand:'tasklist') asStringCollection.
        sepIdx := lines findFirst:[:line | line startsWith:'=='].
        sepIdx == 0 ifTrue:[ ^ #() ].
        entries := (lines from:(sepIdx + 1)) 
                        collect:[:line |
                            |s idx executableName processID userName|

                            s := line readStream.
                            executableName := (s upToMatching:[:ch | ch isDigit]) withoutSeparators.
                            processID := Integer readFrom:s.
                            s skipSeparators.
                            userName := s nextAlphaNumericWord.

                            ProcessListEntry executableName:executableName processID:processID sessionName:userName
                        ]
                        as:OrderedCollection.
    ] ifFalse:[
        lines := (PipeStream outputFromCommand:'ps') asStringCollection.
        sepIdx := lines findFirst:[:line | line withoutSeparators first isDigit].
        sepIdx == 0 ifTrue:[ ^ #() ].
        entries := (lines from:(sepIdx + 1)) 
                        collect:[:line |
                            |s idx executableName processID tty time|

                            s := line readStream.
                            processID := Integer readFrom:s.
                            s skipSeparators.
                            tty := s upToSeparator.
                            s skipSeparators.
                            time := s upToSeparator.
                            s skipSeparators.
                            executableName := s upToEnd.
                            (executableName startsWith:'-') ifTrue:[
                                executableName := executableName copyFrom:2.
                            ].    
                            ProcessListEntry executableName:executableName processID:processID sessionName:nil
                        ]
                        as:OrderedCollection.
    ].
    ^ entries

    "
     self getTaskList
    "

    "Modified: / 16-07-2018 / 23:11:05 / Claus Gittinger"
! !

!OSProcess methodsFor:'accessing'!

auxStream
    ^ auxStream
!

auxStream:something
    "set an auxiliary input stream that will be available to the command as
     file descriptor 3"

    auxStream := something.

    "Modified (comment): / 23-02-2017 / 10:56:57 / Maren"
!

command
    "the OS (shell-) command"

    ^ command

    "Created: / 10.11.1998 / 21:27:07 / cg"
!

command:aStringOrArray 
    "set the command to be executed.

     If aStringOrArray is a String, the commandString is passed to a shell for execution
     - see the description of 'sh -c' in your UNIX manual ('cmd.exe' in your Windows manual).
     With an empty command, the shell will read commands from the passed input stream.

     If aCommandString is an Array, the first element is the command to be executed,
     and the other elements are the arguments to the command. 
     No shell is invoked in this case."
    
    command := aStringOrArray.
!

command:commandStringArg directory:stringOrFilenameArg
    "set the command to be executed and directory, where to execute.
     If aStringOrArray is a String, the commandString is passed to a shell for execution
     - see the description of 'sh -c' in your UNIX manual ('cmd.exe' in your Windows manual).
     If aCommandString is an Array, the first element is the command to be executed,
     and the other elements are the arguments to the command. No shell is invoked in this case."

    command := commandStringArg.
    directory := stringOrFilenameArg.
!

command:commandArg environment:environmentArg directory:directoryArg inStream:inStreamArg outStream:outStreamArg errorStream:errorStreamArg 
    "set the command to be executed & directory, where to execute.
     and input/output streams.
     See comments in individual setters for more info"

    command := commandArg.
    environment := environmentArg.
    directory := directoryArg.
    inStream := inStreamArg.
    outStream := outStreamArg.
    errorStream := errorStreamArg.

    "Created: / 04-11-2018 / 18:28:24 / Claus Gittinger"
!

command:commandArg environment:environmentArg directory:directoryArg inStream:inStreamArg outStream:outStreamArg errorStream:errorStreamArg auxStream:auxStreamArg showWindow:showWindowArg lineWise:lineWiseArg 
    "set the command to be executed & directory, where to execute.
     and input/output streams.
     See comments in individual setters for more info"

    command := commandArg.
    environment := environmentArg.
    directory := directoryArg.
    inStream := inStreamArg.
    outStream := outStreamArg.
    errorStream := errorStreamArg.
    auxStream := auxStreamArg.
    showWindow := showWindowArg.
    lineWise := lineWiseArg.
!

directory
    "the directory where executed"

    ^ directory

    "Created: / 10.11.1998 / 21:21:52 / cg"
!

directory:aStringOrFilename
    "set the directory that will be set as the current directory of the command to be executed"

    directory := aStringOrFilename.
!

environment
    "the shell environment"

    ^ environment

    "Created: / 10.11.1998 / 21:26:34 / cg"
!

environment:aDictionary
    "set the environment variables of the command to be executed"

    environment := aDictionary.
!

errorStream
    ^ errorStream

    "Created: / 10.11.1998 / 21:26:34 / cg"
!

errorStream:aStream
    "set the stream where the stderr output of the command is directed to"

    errorStream := aStream.
!

exitStatus
    "answer the exit status of the command or nil, if the command has not yet been finished"

    ^ exitStatus
!

exitStatus:something
    "set the value of the instance variable 'exitStatus' (automatically generated)"

    exitStatus := something.

    "Created: / 10.11.1998 / 21:24:55 / cg"
!

finishSema
    "wait on this semaphore if you want to wait until the OS process has finished.
     There may be multiple waiters, so it is a good idea to do a #waitUncounted"

    ^ finishSema

    "Modified (comment): / 23-02-2017 / 10:53:17 / Maren"
!

inStream
    ^ inStream

    "Created: / 10.11.1998 / 21:26:34 / cg"
!

inStream:aStream
    "set the stream where the stdin input of the command is read from"

    inStream := aStream.
!

lineWise
    ^ lineWise
!

lineWise:aBoolean
    "When setting to true, read linewise from the command's output and error.
     This is a bit slower than lineWise = false.

     You may use it also when streaming to e.g. Transcript"

    lineWise := aBoolean.
!

newPgrp
    ^ newPgrp
!

newPgrp:aBoolean
    "if aBoolean is true, a new process group will be created for the command and its subprocesses"

    newPgrp := aBoolean.
!

numericPid
    "answer the pid of the process the command is running in,
     or nil if the command has not yet been started.
     Always return an integer, even in windows where pid is a handle-"

    pid isOsHandle ifTrue:[
        ^ pid pid.
    ].
    ^ pid.  "Integer or nil"

    "Created: / 19-07-2018 / 16:21:25 / Stefan Vogel"
    "Modified (comment): / 20-11-2018 / 16:50:26 / Stefan Vogel"
!

outStream
    "the stream where the stdout output of the command is directed to"

    ^ outStream

    "Created: / 10.11.1998 / 21:26:34 / cg"
!

outStream:aStream
    "set the stream where the stdout output of the command is directed to"

    outStream := aStream.
!

pid
    "answer the pid of the process the command is running in,
     or nil if the command has not yet been started.
     Notice: on Unix, the pid is an integer;
     on Windows, it is a handle."

    ^ pid
!

showWindow
    ^ showWindow
!

showWindow:aBooleanOrNil
    "This parameter is ignored on Unix systems.

     You can control (have to - sigh) if a window should be shown for the command or not.
     This is the OS's H_SHOWWINDOW argument.
     If you pass nil as showWindow-argument, the OS's default is used for the particular
     command, which is correct most of the time: i.e. a notepad will open its window, other (non-UI)
     executables will not.
     However, some command-line executables show a window, even if they should not.
     (and also, there seems to be an inconsistency between windows7 and newer windows: in newer,
     a shell command opens a cmd-window, whereas in windows7 it did not)
     In this case, pass an explicit false argument to suppress it."

    showWindow := aBooleanOrNil.
!

terminateActionBlock
    "the (user provided) callback block,
     that will be executed when the command has finished or was terminated.
     If non-nil, it will be called with optional argument:status and:self, the OSProcess."

    ^ terminateActionBlock

    "Modified (comment): / 22-05-2018 / 12:21:24 / Claus Gittinger"
!

terminateActionBlock:aBlock
    "set the callback block,
     that will be called when the command has finished or was terminated.
     If non-nil, it will be called with optional argument:status and:self, the OSProcess.
     WARNING: 
        if the active-process calling #startProcess is already dead (i.e. terminated),
        this callback will be called by the scheduler;
        otherwise, the calling process will be interrupted to perform this callback.
        Therefore: do not open any GUI or other blocking actions in it."

    terminateActionBlock := aBlock.

    "Modified (comment): / 22-05-2018 / 12:42:21 / Claus Gittinger"
! !

!OSProcess methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    showWindow := false.    "/ for backward compatibility
    lineWise := false.
    newPgrp := true.
! !


!OSProcess methodsFor:'printing'!

printOn:aStream
    aStream 
        nextPutAll:self className;
        nextPut:$(.
    exitStatus notNil ifTrue:[
        exitStatus printOn:aStream.
    ] ifFalse:[    
        pid printOn:aStream.
    ].        
    aStream space.
    command printOn:aStream.
    aStream nextPut:$)

    "Modified: / 23-01-2019 / 13:55:08 / Claus Gittinger"
! !

!OSProcess methodsFor:'private'!

releasePid
    "only used in Windows, where pid is a handle that must be released"

    |pidHandle|

    pidHandle := pid.
    pidHandle isOsHandle ifFalse:[
        ^ self.
    ].

    pid := pidHandle pid.   "remember the numeric value"
    pidHandle close.
!

setupShufflerForInput:aStream
    "if aStream is an internal Stream, set up a pipe for the command input.
     Start a process that shuffles the data from the internal stream into the pipe
     (and into the command's input).
     Return the ExternalStream that should be passed to the OS process."

    |pipe externalStream shuffledStream shufflerProcess|

    (aStream isNil or:[aStream isExternalStream]) ifTrue:[
        ^ aStream.
    ].

    pipe := PipeStream makePipe.
    externalStream := pipe at:1.
    shuffledStream := pipe at:2.
    shuffledStream setCommandString:('Stdin of: ', command printString).
    lineWise ifFalse:[
        shuffledStream blocking:false.
    ].
    aStream isBinary ifTrue:[
        shuffledStream binary.
    ].

    "/ start a reader process, shuffling data from the given
    "/ inStream to the pipe (which is connected to the commands input)
    shufflerProcess := 
        [
            [
                lineWise ifTrue:[
                    "shuffle until end-of-input"
                    [aStream atEnd] whileFalse:[
                        |data|

                        data := aStream nextLine.
                        data notNil ifTrue:[
                            shuffledStream nextPutLine:data.
                            shuffledStream flush.
                        ].
                    ].
                ] ifFalse:[
                    aStream copyToEndInto:shuffledStream.
                ].
            ] on:WriteError do:[:ex|
                "ignore"
            ] ensure:[
                shuffledStream close.
            ]
        ] newProcess
            name:'OSProcess: input shuffler';
"/                beSystemProcess;
            resume.

    inputShufflerProcesses isNil ifTrue:[
        inputShufflerProcesses := OrderedCollection new:2.
    ].
    inputShufflerProcesses add:shufflerProcess.
    streamsToClose add:externalStream.

    ^ externalStream

    "Modified: / 31-01-2017 / 16:50:39 / stefan"
    "Modified (comment): / 23-02-2017 / 10:51:34 / Maren"
    "Modified: / 29-10-2018 / 15:35:01 / Claus Gittinger"
    "Modified: / 01-11-2018 / 14:40:12 / Stefan Vogel"
!

setupShufflerForOutput:aStream
    "if aStream is an internal Stream, set up a pipe for the command output.
     Start a process that shuffles the data from the pipe's output
     into the internal stream.
     Return the ExternalStream that should be passed to the OS process."

    |pipe externalStream shuffledStream shufflerProcess|

    (aStream isNil or:[aStream isExternalStream]) ifTrue:[
        ^ aStream.
    ].

    pipe := PipeStream makePipe.
    externalStream := pipe at:2.
    shuffledStream := pipe at:1.
    shuffledStream setCommandString:('Stdout/err of: ', command printString).
    aStream isBinary ifTrue:[
        shuffledStream binary.
    ].

    shufflerProcess := 
        [
            [
                "shuffle until the pipe closes"
                lineWise ifTrue:[
                    [shuffledStream atEnd] whileFalse:[
                        |data|

                        data := shuffledStream nextLine.
                        data notNil ifTrue:[
                            aStream nextPutLine:data
                        ].
                    ].
                ] ifFalse:[
                    shuffledStream copyToEndInto:aStream.
                ].
            ] on:WriteError do:[:ex |
                "ignore" 
            ] ensure:[
                shuffledStream close.
            ].
        ] newProcess
            priority:(Processor userSchedulingPriority "+ 1");
            name:'OSProcess: output shuffler';
"/                beSystemProcess;
            resume.

    outputShufflerProcesses isNil ifTrue:[
        outputShufflerProcesses := OrderedCollection new:2.
    ].
    outputShufflerProcesses add:shufflerProcess.
    streamsToClose add:externalStream.

    ^ externalStream

    "Modified: / 31-01-2017 / 16:57:25 / stefan"
    "Modified (comment): / 29-10-2018 / 16:00:55 / Claus Gittinger"
    "Modified: / 01-11-2018 / 14:40:24 / Stefan Vogel"
!

startCommand
    "the 'real' command to be executed.
     Redefined for remote processes (eg. to construct a remote command string).
     Command may be both an Array or a String"
    
    ^ command

    "Modified (comment): / 22-05-2018 / 12:37:38 / Stefan Vogel"
!

terminateShufflerProcesses
    "terminate all the running shuffler processes"

    self 
        terminateShufflerProcesses:inputShufflerProcesses;
        terminateShufflerProcesses:outputShufflerProcesses.

    inputShufflerProcesses := outputShufflerProcesses := nil.

    "Created: / 01-11-2018 / 14:16:51 / Stefan Vogel"
    "Modified: / 01-11-2018 / 15:37:16 / Stefan Vogel"
!

terminateShufflerProcesses:aProcessCollection
    "terminate the running shuffler processes contained in aProcessCollection"

    |procs|

    procs := aProcessCollection.
    procs notNil ifTrue:[
        procs do:[:eachProc | eachProc terminate].
        procs removeAll.
    ].

    "Created: / 01-11-2018 / 14:35:51 / Stefan Vogel"
    "Modified: / 01-11-2018 / 15:36:12 / Stefan Vogel"
! !

!OSProcess methodsFor:'queries'!

finishedWithSuccess
    ^ exitStatus notNil and:[exitStatus success].
!

isAlive
    "answer true if the process is still alive"

    ^ pid notNil and:[exitStatus isNil]

    "Modified (comment): / 23-02-2017 / 10:52:37 / Maren"
!

isDead
    "answer true if the process is no longer alive"

    ^ self isAlive not

    "Modified (comment): / 23-02-2017 / 10:52:31 / Maren"
! !

!OSProcess methodsFor:'starting'!

execute
    "execute the command. 
     Wait until it is finished.
     Abort the execution if I am interrupted.
     Answer true if it terminated successfully, 
     false if it could not be started or terminated with error."

    |ok|

    [
        ok := self startProcess.
        ok ifTrue:[
            self waitUntilFinished.
            ok := self finishedWithSuccess.
        ].
        "if we come here, all streamsToClose have been closed 
         and all shuffler processses are terminated"
    ] ifCurtailed:[
        "we have been interrupted -
         terminate the os-command (and all of its forked commands), and clean up"
        |streams|

        pid notNil ifTrue:[
            self terminateGroup.
        ].
        (streams := streamsToClose) notNil ifTrue:[
            Logger info:'closing leftover streams'.
            streamsToClose := nil.
            streams do:[:eachStream | eachStream close].
        ].
        self terminateShufflerProcesses.
    ].

    ^ ok.

    "Modified: / 29-10-2018 / 15:59:33 / Claus Gittinger"
    "Modified: / 31-10-2018 / 12:31:42 / Maren"
    "Modified (format): / 01-11-2018 / 15:00:01 / Stefan Vogel"
!

startProcess
    "Start the command asynchronously (i.e. don't wait until is has finished).
     If there are non-external streams, setup transfer (shuffler) processes
     to transfer data from a pipe to the internal stream.

     Answer true if the command could started succesfully, false if not.

     NOTE: under normal circumstances, even if the command cannot be found,
           the exit fom the command interpreter/shell is done some time later
           So you have to check later or set #terminateActionBlock: and check there."

    |externalInStream externalAuxStream externalErrorStream externalOutStream callingProcess|

    streamsToClose := OrderedCollection new:4.

    externalInStream := self setupShufflerForInput:inStream.
    externalAuxStream := self setupShufflerForInput:auxStream.
    externalOutStream := self setupShufflerForOutput:outStream.

    errorStream == outStream ifTrue:[
        externalErrorStream := externalOutStream.
    ] ifFalse:[
        externalErrorStream := self setupShufflerForOutput:errorStream.
    ].

    "start the command"
    finishSema := EventSemaphore new.

    "/ UserPreferences current logExecutedOSCommands:true
    UserPreferences current logExecutedOSCommands ifTrue:[
        Transcript showCR:(('OS command: ', self startCommand printString) withColor:Color brown).  
    ].

    callingProcess := Processor activeProcess.
    
    Processor 
        monitor:[
            pid := OperatingSystem
                        startProcess:(self startCommand)
                        inputFrom:externalInStream
                        outputTo:externalOutStream
                        errorTo:externalErrorStream
                        auxFrom:externalAuxStream
                        environment:environment
                        inDirectory:directory
                        newPgrp:newPgrp
                        showWindow:showWindow.
        ] 
        action:[:status |
            status stillAlive ifFalse:[
                exitStatus := status.
                self terminate.

                finishSema signal.
                terminateActionBlock notNil ifTrue:[
                    callingProcess isDead ifTrue:[
                        Error catch:[
                            "don't bother ProcessorScheduler with errors from terminateActionBlock!!"
                            terminateActionBlock valueWithOptionalArgument:status and:self.
                        ].
                    ] ifFalse:[
                        callingProcess 
                            interruptWith:[
                                terminateActionBlock valueWithOptionalArgument:status and:self.
                            ]        
                    ].    
                ].

                self releasePid.

                UserPreferences current logExecutedOSCommands ifTrue:[
                    Transcript 
                        showCR:(('OS command finished: %1 status: %2'
                                    bindWith: self startCommand
                                    with:status code)     
                                    withColor:(
                                        status success 
                                            ifTrue:[Color darkGreen]
                                            ifFalse:[Color red])).  
                ].
            ].
        ].

    "we can close the remote side of the pipes after the os process has been started (after the fork)"
    streamsToClose do:[:eachStream | eachStream close].
    streamsToClose := nil.

    "/ nil those references here, because there is still a home-context reference from the
    "/ monitor-pid action block. Otheriwse, the garbage collector might not collect them.
    externalInStream := externalAuxStream := externalOutStream := externalErrorStream := nil.
    
    pid isNil ifTrue:[
        UserPreferences current logExecutedOSCommands ifTrue:[
            Transcript 
                showCR:(('OS command failed: %1'
                            bindWith: self startCommand)     
                            withColor:(Color red)).  
        ].

        "process could not be started - terminate shufflers"
        self terminateShufflerProcesses.

        exitStatus := OperatingSystem osProcessStatusClass processCreationFailure.
        finishSema signal.
        terminateActionBlock notNil ifTrue:[
            terminateActionBlock valueWithOptionalArgument:exitStatus and:self.
        ].
        ^ false.
    ].

    ^ true.

    "Modified: / 01-11-2018 / 14:41:12 / Stefan Vogel"
    "Modified: / 13-03-2019 / 21:13:05 / Claus Gittinger"
! !

!OSProcess methodsFor:'terminating'!

kill
    "kill the process - the process does not get the chance to clean up"
    
    pid notNil ifTrue:[
        OperatingSystem killProcess:pid.
    ].
!

killGroup
    "kill the processGroup - the processes do not get the chance to clean up"

    pid notNil ifTrue:[
        OperatingSystem 
            killProcessGroup:pid;
            killProcess:pid.
    ].
!

terminate
    "terminate the process gracefully"

    pid notNil ifTrue:[
        OperatingSystem terminateProcess:pid.
    ].
!

terminateGroup
    "terminate the process group.
     Under Windows, this is the same as terminateWithAllChildren,
     under unix, this terminates a subset of all children"

    pid notNil ifTrue:[
        OperatingSystem 
            terminateProcess:pid;
            terminateProcessGroup:pid.
    ].

    "Modified (comment): / 23-02-2017 / 10:50:13 / Maren"
    "Modified: / 09-03-2017 / 15:00:58 / stefan"
! !

!OSProcess methodsFor:'waiting'!

waitUntilFinished
    <resource: #skipInDebuggersWalkBack>

    "wait with a veryy long timeout, 
     in order that ProcessorScheduler>>#checkForEndOfDispatch recognizes
     this waiting process as an user process which is still alive.
     The timeout is meant to never occur!!"

    ^ self waitUntilFinishedWithTimeout:60*60*24000

    "Modified: / 01-08-2017 / 14:41:10 / stefan"
    "Modified (comment): / 01-08-2017 / 17:15:55 / stefan"
    "Modified: / 30-05-2018 / 13:57:42 / Claus Gittinger"
    "Modified (comment): / 01-11-2018 / 14:43:46 / Stefan Vogel"
!

waitUntilFinishedWithTimeout:timeout
    <resource: #skipInDebuggersWalkBack>

    |processList|

    (finishSema waitWithTimeout:timeout) isNil ifTrue:[
        "timed out"
        ^ nil.
    ].

    "have to wait until the output shufflers shuffling command's outputs have finished their work"
    processList := outputShufflerProcesses.
    processList notNil ifTrue:[
        processList do:[:eachProcess | 
            eachProcess waitUntilTerminated.
        ].
        outputShufflerProcesses := nil.
    ].

    "command has finished and is no longer reading from its inputs"
    inputShufflerProcesses notNil ifTrue:[
        self terminateShufflerProcesses:inputShufflerProcesses.
        inputShufflerProcesses := nil.
    ].

    "Modified: / 30-05-2018 / 13:57:39 / Claus Gittinger"
    "Modified: / 01-11-2018 / 15:53:09 / Stefan Vogel"
! !

!OSProcess::ProcessListEntry class methodsFor:'documentation'!

documentation
"
    documentation to be added.

    [author:]
        anharman

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!OSProcess::ProcessListEntry class methodsFor:'instance creation'!

executableName:executableNameArg processID:processIDArg sessionName:sessionNameArg 
    ^ self new executableName:executableNameArg processID:processIDArg sessionName:sessionNameArg 
!

executableName:executableNameArg processID:processIDArg userName:userNameArg 
    ^ self new executableName:executableNameArg processID:processIDArg userName:userNameArg 
! !

!OSProcess::ProcessListEntry methodsFor:'accessing'!

executableName
    ^ executableName
!

executableName:executableNameArg processID:processIDArg sessionName:sessionNameArg 
    executableName := executableNameArg.
    processID := processIDArg.
    sessionName := sessionNameArg.
!

executableName:executableNameArg processID:processIDArg userName:userNameArg 
    executableName := executableNameArg.
    processID := processIDArg.
    userName := userNameArg.
!

processID
    ^ processID
!

userName
    ^ userName
! !

!OSProcess::ProcessListEntry methodsFor:'printing & storing'!

printOn:aStream
    aStream nextPutAll:('(process: %1 pid: %2)' bindWith:executableName with:processID)
! !

!OSProcess::RemoteOSProcess class methodsFor:'documentation'!

documentation
"
    Instances of OSProcess represent operating system processes that can be executed.
    (as opposed to Smalltalk processes).

    [author:]
        cg

    [instance variables:]
        host        String          the host on which to execute the command

    [class variables:]

    [see also:]
        Process
"
!

examples
"
                                                            [exBegin]
    |outStream|

    outStream := '' writeStream.

    (OSProcess onHost:'exeptn') 
        command:'ls -l';
        inStream:'abc' readStream;
        outStream:outStream;
        lineWise:true;
        execute.

    outStream contents
                                                            [exEnd]
"
! !

!OSProcess::RemoteOSProcess methodsFor:'accessing'!

host
    ^ host
!

host:aHostName
    host := aHostName.
! !

!OSProcess::RemoteOSProcess methodsFor:'private'!

startCommand
    "the 'real' command"

    "for now, always use ssh; 
     later, this should be configurable, 
     which remote mechanism is to be used per host"
     
    ^ 'ssh %1 "%2"' bindWith:host with:command
! !

!OSProcess class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


OSProcess initialize!