OSProcess.st
author fm
Tue, 29 Sep 2009 13:03:41 +0200
changeset 127 80e7f454b687
parent 126 84a323ae6ac3
child 355 11af87ccad10
permissions -rw-r--r--
*** empty log message ***

"{ Package: 'cvut:stx/goodies/libsvn' }"

Object subclass:#OSProcess
	instanceVariableNames:'executable arguments environment workdir stdin stdout stderr
		exitValue runningLock'
	classVariableNames:''
	poolDictionaries:''
	category:'OS-Support'
!


!OSProcess class methodsFor:'private'!

asShellQuotedArgument: anObject

    | aString unquotedStream quotedStream |
    aString := anObject asString.

    (aString first = $' and: [aString last = $'])
        ifTrue:[^aString].

    (aString first = $" and: [aString last = $"])
        ifTrue:[^aString].

    (aString allSatisfy:
        [:char|char isSeparator not and: [(#($" $< $> $& $# $; $\) includes: char) not]])
            ifTrue:[^aString].

    unquotedStream := aString readStream.
    quotedStream := (String new: aString size + 10) writeStream.
    quotedStream nextPut: $".
    [ unquotedStream atEnd ] whileFalse:
        [|char|
        char := unquotedStream next.
        (#($" $\) includes: char) ifTrue:[quotedStream nextPut: $\].
        quotedStream nextPut: char].
    quotedStream nextPut: $".
    ^quotedStream contents.

    "
        OSProcess asShellQuotedArgument: 'Hello' .
        OSProcess asShellQuotedArgument: 'Hello world'  
        OSProcess asShellQuotedArgument: 'Hello'' world'   
        OSProcess asShellQuotedArgument: 'Hello
        World'
    "

    "Created: / 10-10-2008 / 12:32:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 02-06-2009 / 19:41:05 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!OSProcess methodsFor:'accessing'!

arguments
    ^ arguments ? #()

    "Created: / 15-03-2008 / 18:09:37 / janfrog"
!

arguments:something
    arguments := something.

    "Created: / 15-03-2008 / 18:09:37 / janfrog"
!

environment
    ^ environment

    "Created: / 15-03-2008 / 18:09:37 / janfrog"
!

environment:something
    environment := something.

    "Created: / 15-03-2008 / 18:09:37 / janfrog"
!

executable
    ^ executable

    "Created: / 15-03-2008 / 18:09:37 / janfrog"
!

executable:something
    executable := something.

    "Created: / 15-03-2008 / 18:09:37 / janfrog"
!

exitValue

    self waitFor.
    ^exitValue

    "Created: / 15-03-2008 / 18:08:00 / janfrog"
    "Modified: / 19-04-2008 / 12:25:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

stderr
    ^ stderr ? Stderr

    "Created: / 15-03-2008 / 18:21:05 / janfrog"
!

stderr:something
    stderr := something.

    "Created: / 15-03-2008 / 18:21:05 / janfrog"
!

stdin
    ^ stdin ? Stdin

    "Created: / 15-03-2008 / 18:21:05 / janfrog"
!

stdin:something
    stdin := something.

    "Created: / 15-03-2008 / 18:21:05 / janfrog"
!

stdout
    ^ stdout ? Transcript

    "Created: / 15-03-2008 / 18:21:05 / janfrog"
!

stdout:something
    stdout := something.

    "Created: / 15-03-2008 / 18:21:05 / janfrog"
!

workdir
    ^ workdir ? Filename defaultDirectory

    "Created: / 15-03-2008 / 18:09:37 / janfrog"
!

workdir:aStringOrFilename
    workdir := aStringOrFilename asString.

    "Created: / 15-03-2008 / 18:09:37 / janfrog"
    "Modified: / 09-04-2009 / 17:32:25 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!OSProcess methodsFor:'conversion'!

asShellCommandString

    | cmdStream |
    cmdStream := String new writeStream.
    cmdStream nextPutAll:self executable.
    self arguments do:
        [:arg|
        cmdStream space.
        cmdStream nextPutAll:(self asShellQuotedArgument: arg)].

    ^cmdStream contents utf8Encoded

    "Created: / 19-03-2008 / 12:34:59 / janfrog"
    "Modified: / 31-03-2008 / 14:09:05 / janfrog"
    "Modified: / 23-03-2009 / 10:09:55 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!OSProcess methodsFor:'operations'!

execute
    "
    self synchronized:
        [runningLock 
            ifNotNil:[self error:'Process already running']
            ifNil:[runningLock := Semaphore new:0]].
    [["
        (OperatingSystem
            executeCommand: self asShellCommandString
            inputFrom: self stdin
            outputTo: self stdout
            errorTo: self stderr
            auxFrom: nil
            environment: nil
            inDirectory: self workdir asString
            lineWise: (self stdout = self stderr)
            onError:[:value|exitValue := value code.false])
            ifTrue:[exitValue := 0]        
    "
    ] ensure:[runningLock signalForAll. runningLock := nil]] fork
    "

    "Created: / 15-03-2008 / 18:11:20 / janfrog"
    "Modified: / 19-03-2008 / 12:35:05 / janfrog"
    "Modified: / 08-06-2008 / 19:15:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

waitFor

    "| lock |
    self synchronized:
        [runningLock 
            ifNil:[^self]
            ifNotNil:[lock := runningLock]].
    lock wait"

    "Created: / 15-03-2008 / 18:32:41 / janfrog"
    "Modified: / 08-06-2008 / 19:15:22 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!OSProcess methodsFor:'private'!

asShellQuotedArgument:arg
    ^ self class asShellQuotedArgument:arg

    "Created: / 10-10-2008 / 12:32:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!OSProcess class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^'Id: OSProcess.st 88 2009-06-15 12:12:29Z vranyj1 '
! !