OSProcess.st
author Stefan Vogel <sv@exept.de>
Thu, 22 Dec 2016 22:06:20 +0100
changeset 21182 001704ae8bbf
parent 21181 a8a9220ed86f
child 21183 fdeb19204fb2
permissions -rw-r--r--
#REFACTORING by stefan class: OSProcess class definition added: #newPgrp #newPgrp: removed: #getProcessHandle #isExecutable: #killWithAllChildren #parentPid #parentPid: #terminateWithAllChildren comment/format in: #documentation #examples changed: #execute #initialize #setupShufflerForInput: #setupShufflerForOutput: #startProcess

"{ 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 terminateLock shuffleRest'
	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
    "
! !

!OSProcess class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!OSProcess class methodsFor:'initialize'!

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

!OSProcess class methodsFor:'private shuffling'!

shuffleAllFrom:anInStream to:anOutStream lineWise:lineWise lockWith:aLock
    lineWise ifFalse:[
        ^ anInStream copyToEndInto:anOutStream.
    ].
    [anInStream atEnd] whileFalse:[
        aLock critical:[
            self
                shuffleFrom:anInStream
                to:anOutStream
                lineWise:lineWise
        ]
    ]
!

shuffleFrom:anInStream to:anOutStream lineWise:lineWise
    "copy data from anInStream to anOutStream.
     Caller makes sure, than anInStream does not block.
     anOutstream should have been set to non-blocking-mode"

    lineWise ifTrue:[
	|data|

	data := anInStream nextLine.
	data notNil ifTrue:[
	    anOutStream nextPutLine:data
	] .
    ] ifFalse:[
	anInStream copyToEndInto:anOutStream.
    ].
!

shuffleRestFrom:anInStream to:anOutStream lineWise:lineWise
    [anInStream atEnd] whileFalse:[
	self
	    shuffleFrom:anInStream
	    to:anOutStream
	    lineWise:lineWise.
    ].
! !

!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
    "return the value of the instance variable 'finishSema' (automatically generated)"

    ^ finishSema

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

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

    finishSema := something.

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

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 := true.
    newPgrp := false.
! !

!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 := [
            [
                [aStream atEnd] whileFalse:[
                    self class shuffleFrom:aStream to:shuffledStream lineWise:lineWise.
                    shuffledStream flush
                ]
            ] ensure:[
                shuffledStream close.
            ]
        ] newProcess
            name:'OSProcess input shuffler';
"/                beSystemProcess;
            resume.

    shufflerProcesses add:shufflerProcess.
    ^ 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:[
                [
                    self class shuffleAllFrom:shuffledStream to:aStream lineWise:lineWise lockWith:terminateLock.
                ] ensure:[
                    externalStream close.
                    shuffleRest ifTrue:[
                        self class shuffleRestFrom:shuffledStream to:aStream lineWise:lineWise
                    ].
                    shuffledStream close.
                ].
            ].
        ] newProcess
            priority:(Processor userSchedulingPriority "+ 1");
            name:'OSProcess output shuffler';
"/                beSystemProcess;
            resume.

    shufflerProcesses add:shufflerProcess.
    ^ 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

    |nullStream streamsToClose newStream|

    terminateLock := Semaphore forMutualExclusion.
    shufflerProcesses := OrderedCollection new.
    streamsToClose := OrderedCollection new:2.
    shuffleRest := false.

    newStream := self setupShufflerForInput:inStream.
    newStream ~~ inStream ifTrue:[
        inStream := newStream.
        streamsToClose add:newStream.
    ].
    newStream := self setupShufflerForInput:auxStream.
    newStream ~~ auxStream ifTrue:[
        auxStream := newStream.
        streamsToClose add:newStream.
    ].
    outStream := self setupShufflerForOutput:outStream.
    errorStream := self setupShufflerForOutput:errorStream.

    [
        "make sure, that the command gets a stdin, stdout and stderr"
        inStream isNil ifTrue:[
            inStream := nullStream := Filename nullDevice readWriteStream.
        ].
        outStream isNil ifTrue:[
            nullStream isNil ifTrue:[nullStream := Filename nullDevice writeStream].
            outStream := nullStream.
        ].
        errorStream isNil ifTrue:[
            errorStream := outStream
        ].

        "start the command"
        self startProcess ifTrue:[
            finishSema wait.
            shuffleRest := true.
        ].
    ] ensure:[
        (shuffleRest not and:[pid notNil]) ifTrue:[
            "/ we were interrupted -
            "/ terminate the os-command (and all of its forked commands)
            self terminateGroup; terminate.
            OperatingSystem closePid:pid.
        ].
        shufflerProcesses do:[:eachProcess|
            "terminate the shuffler processes.
             They close the pipe and read the rest from the pipe when being terminated"
            terminateLock critical:[eachProcess terminate].
            eachProcess waitUntilTerminated.
        ].
        shufflerProcesses := nil.
        streamsToClose do:[:eachStream | eachStream close].
        nullStream notNil ifTrue:[
            nullStream close.
        ].
    ].

    (exitStatus isNil or:[exitStatus success]) ifFalse:[
        ^ false
    ].
    ^ true
!

startProcess
    finishSema := Semaphore new.

    Processor 
        monitor:[
            pid := OperatingSystem
                startProcess:command
                inputFrom:inStream
                outputTo:outStream
                errorTo:errorStream
                auxFrom:auxStream
                environment:environment
                inDirectory:directory
                newPgrp:newPgrp
                showWindow:showWindow.
        ] 
        action:[:status |
            status stillAlive ifFalse:[
                exitStatus := status.
                pid notNil ifTrue:[
                    OperatingSystem closePid:pid.
                ].
                finishSema signal
            ].
        ].

    pid isNil ifTrue:[
        exitStatus := OperatingSystem osProcessStatusClass processCreationFailure.
        ^ false
    ].

    ^ true.

    "Created: / 10.11.1998 / 21:23:50 / cg"
    "Modified: / 10.11.1998 / 21:33:16 / cg"
! !

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

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

!OSProcess class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


OSProcess initialize!