OSProcess.st
author Stefan Vogel <sv@exept.de>
Thu, 22 Dec 2016 14:56:04 +0100
changeset 21172 36a0e5430705
parent 20379 135c4fc19014
child 21181 a8a9220ed86f
permissions -rw-r--r--
#FEATURE by stefan class: OSProcess class definition added:18 methods removed: #commandLine #commandLine: variable renamed in: #printOn: THis replaces now the functionality ion Win32Process

"{ Package: 'stx:libbasic' }"

"{ NameSpace: Smalltalk }"

Object subclass:#OSProcess
	instanceVariableNames:'pid parentPid command environment directory inStream outStream
		errorStream exitStatus finishSema'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Support'
!

!OSProcess class methodsFor:'documentation'!

documentation
"
    OSProcess is an abstract class. Instances represent operating system processes
    (as opposed to Smalltalk processes).

    [author:]
        Stefan Vogel (stefan@zwerg)

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

    [class variables:]

    [see also:]
        Process

"
! !

!OSProcess class methodsFor:'initialize'!

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

!OSProcess methodsFor:'accessing'!

accessor
    ^ self
!

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

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

parentPid
    ^ parentPid
!

parentPid:something
    parentPid := something.
!

pid
    ^ pid
!

pid:something
    pid := something.
! !

!OSProcess methodsFor:'file queries'!

isExecutable:aPathName
    ^ aPathName asFilename isExecutable
! !

!OSProcess methodsFor:'printing'!

printOn:aStream
    aStream 
        nextPutAll:self className;
        nextPut:$(.
    pid printOn:aStream.
    aStream space.
    command printOn:aStream.
    aStream nextPut:$)
! !

!OSProcess methodsFor:'queries'!

getProcessHandle
    "some OperatingSystems redefine this to resolve this to a processHandle
     (which must be explicitely freed later).
     Others simply return the pid here"

    ^ self subclassResponsibility
!

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

    ^ self subclassResponsibility
!

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

    ^ self isAlive not
! !

!OSProcess methodsFor:'starting'!

startProcess
    finishSema := Semaphore new.

    Processor 
        monitor:[
            pid := OperatingSystem
                startProcess:command
                inputFrom:inStream
                outputTo:outStream
                errorTo:errorStream
                auxFrom:nil
                environment:nil
                inDirectory:directory
                showWindow:false.
        ] 
        action:[:status |
            status stillAlive ifFalse:[
                exitStatus := status.
                "/ paranoia?
                pid notNil ifTrue:[
                    OperatingSystem terminateProcessGroup:pid.
                    OperatingSystem terminateProcess:pid.
                    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"
    
    ^ self subclassResponsibility.
!

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

    ^ self subclassResponsibility.
!

killWithAllChildren
    "terminate gracefully the process with all of its child processes"

    ^ self subclassResponsibility.
!

terminate
    "terminate the process gracefully"

    ^ self subclassResponsibility.
!

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

   ^ self subclassResponsibility.
!

terminateWithAllChildren
    "terminate gracefully the process with all of its child processes"

    ^ self subclassResponsibility.
! !

!OSProcess class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


OSProcess initialize!