OSProcess.st
author HG Automerge
Mon, 26 Dec 2016 10:13:07 +0000
branchjv
changeset 21247 9ee1206fc247
parent 20398 8cb53f870d39
parent 21185 b2ecc061106c
child 21249 86c01ee5a76e
permissions -rw-r--r--
Merge

"{ Encoding: utf8 }"

"{ Package: 'stx:libbasic' }"

"{ NameSpace: Smalltalk }"

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

!OSProcess class methodsFor:'documentation'!

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

    [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
    "
        |outStream|

        outStream := '' writeStream.

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

        outStream contents
    "

    "
        |outStream|

        outStream := '' writeStream.

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

        outStream inspect
    "

    "
        |outStream|

        outStream := '' writeStream.

        self new 
            command:'ls -l & ls -l >&2';
            inStream:'abc' readStream;
            outStream:outStream;
            errorStream:outStream;
            startProcess.

        outStream inspect
    "
! !

!OSProcess class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!OSProcess class methodsFor:'initialize'!

initialize
    "Backward compatibility"
    Win32Process := self.
! !

!OSProcess methodsFor:'accessing'!

accessor
    ^ self
!

auxStream
    ^ auxStream
!

auxStream:something
    auxStream := something.
!

command
    "return the value of the instance variable 'command' (automatically generated)"

    ^ command

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

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

    command := something.

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

directory
    "return the value of the instance variable 'directory' (automatically generated)"

    ^ directory

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

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

    directory := something.

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

environment
    "return the value of the instance variable 'environment' (automatically generated)"

    ^ environment

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

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

    environment := something.

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

errorStream
    "return the value of the instance variable 'errorStream' (automatically generated)"

    ^ errorStream

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

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

    errorStream := something.

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

exitStatus
    "return the value of the instance variable 'exitStatus' (automatically generated)"

    ^ exitStatus

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

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 yo 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
!

inStream
    "return the value of the instance variable 'inStream' (automatically generated)"

    ^ inStream

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

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

    inStream := something.

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

lineWise
    ^ lineWise
!

lineWise:something
    lineWise := something.
!

newPgrp
    ^ newPgrp
!

newPgrp:something
    newPgrp := something.
!

outStream
    "return the value of the instance variable 'outStream' (automatically generated)"

    ^ outStream

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

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

    outStream := something.

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

pid
    ^ pid
!

pid:something
    pid := something.
!

showWindow
    ^ showWindow
!

showWindow:something
    showWindow := something.
! !

!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:$(.
    pid printOn:aStream.
    aStream space.
    command printOn:aStream.
    aStream nextPut:$)
! !

!OSProcess methodsFor:'private'!

setupShufflerForInput:aStream
    "if aStream is an internal Stream, set up a pipe for the command input.
     Start a process that shuffles tha data fron the internal stream into the pipe
     (and into the command's input)."

    |pipe externalStream shuffledStream shufflerProcess|

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

    pipe := NonPositionableExternalStream makePipe.
    externalStream := pipe at:1.
    shuffledStream := pipe at:2.
    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 := [
            [
                WriteError handle:[:ex |"ignored" ] do:[
                    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.
                    ].
                ].
            ] ensure:[
                shuffledStream close.
            ]
        ] newProcess
            name:'OSProcess input shuffler';
"/                beSystemProcess;
            resume.

    shufflerProcesses add:shufflerProcess.
    streamsToClose add:externalStream.

    ^ externalStream
!

setupShufflerForOutput:aStream
    "if aStream is an internal Stream, set up a pipe for the command output.
     Start a process that shuffles the data fron the pipe into the internal stream."

    |pipe externalStream shuffledStream shufflerProcess|

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

    pipe := NonPositionableExternalStream makePipe.
    externalStream := pipe at:2.
    shuffledStream := pipe at:1.
    aStream isBinary ifTrue:[
        shuffledStream binary.
    ].

    shufflerProcess := [
            WriteError handle:[:ex |"ignored" ] do:[
                [
                    "shuffle until the pipe closes"
                    lineWise ifTrue:[
                        [shuffledStream atEnd] whileFalse:[
                            |data|

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

    streamsToClose add:externalStream.

    ^ externalStream
! !

!OSProcess methodsFor:'queries'!

isAlive
    "answer true, if the process is still alive"

    ^ pid notNil and:[exitStatus notNil]
!

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

    ^ self isAlive not
! !

!OSProcess methodsFor:'starting'!

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

    |ok|

    [
        ok := self startProcess.
        ok ifTrue:[
            ok := self waitUntilFinished.
        ].
    ] ifCurtailed:[
        "/ we were interrupted -
        "/ terminate the os-command (and all of its forked commands)
        pid notNil ifTrue:[
            self terminateGroup.
        ].
    ].
    ^ ok.
!

startProcess
    "If there are non-external streams, setup transfer (shuffler) processes
     to transfer data from a pipe to the internal stream.
     Start the command.
     Answer true if the command could be started, false if not.
     Return immediately (do not wait until the command is finished)." 

    |nullStream externalInStream externalAuxStream externalErrorStream externalOutStream|

    shufflerProcesses := OrderedCollection new.
    streamsToClose := OrderedCollection new:3.

    externalInStream := self setupShufflerForInput:inStream.
    externalAuxStream := self setupShufflerForInput:auxStream.
    errorStream == outStream ifTrue:[
        externalErrorStream := externalOutStream := self setupShufflerForOutput:errorStream.
    ] ifFalse:[
        externalErrorStream := self setupShufflerForOutput:errorStream.
        externalOutStream := self setupShufflerForOutput:outStream.
    ].

    "make sure, that the command gets a stdin, stdout and stderr"
    externalInStream isNil ifTrue:[
        externalInStream := nullStream := Filename nullDevice readWriteStream.
        streamsToClose add:nullStream.
    ].
    externalOutStream isNil ifTrue:[
        nullStream isNil ifTrue:[
            nullStream := Filename nullDevice writeStream.
            streamsToClose add:nullStream.
        ].
        externalOutStream := nullStream.
    ].
    externalErrorStream isNil ifTrue:[
        nullStream isNil ifTrue:[
            nullStream := Filename nullDevice writeStream.
            streamsToClose add:nullStream.
        ].
        externalErrorStream := nullStream.
    ].

    "start the command"
    finishSema := Semaphore new.

    Processor 
        monitor:[
            pid := OperatingSystem
                    startProcess:command
                    inputFrom:externalInStream
                    outputTo:externalOutStream
                    errorTo:externalErrorStream
                    auxFrom:externalAuxStream
                    environment:environment
                    inDirectory:directory
                    newPgrp:newPgrp
                    showWindow:showWindow.
        ] 
        action:[:status |
            status stillAlive ifFalse:[
                exitStatus := status.
                pid notNil ifTrue:[
                    OperatingSystem closePid:pid.
                ].
                shufflerProcesses do:[:eachProcess|
                    "terminate the shuffler processes.
                     They close the local side of the pipe when being terminated"
                    eachProcess terminate.
                ].
                finishSema signal.
            ].
        ].

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

    pid isNil ifTrue:[
        "process could not be started - terminate shufflers"
        shufflerProcesses do:[:eachProcess|
            eachProcess terminate.
        ].
        shufflerProcesses := nil.
        exitStatus := OperatingSystem osProcessStatusClass processCreationFailure.
        ^ false.
    ].

    ^ true.
! !

!OSProcess methodsFor:'terminating'!

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

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

    OperatingSystem 
        killProcessGroup:pid;
        killProcess:pid.
!

terminate
    "terminate the process gracefully"

    OperatingSystem terminateProcess:pid.
!

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

    OperatingSystem 
        terminateProcessGroup:pid;
        terminateProcess:pid.
! !

!OSProcess methodsFor:'waiting'!

waitUntilFinished
    |processList|

    finishSema waitUncounted.

    "have to wait until the shufflers have finished their work"
    shufflerProcesses notEmptyOrNil ifTrue:[
        processList := shufflerProcesses.
        processList do:[:eachProcess | 
            eachProcess waitUntilTerminated.
        ].
        shufflerProcesses := nil.
    ].

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

!OSProcess class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


OSProcess initialize!