SVN__Command.st
author fm
Tue, 29 Sep 2009 17:17:58 +0200
changeset 163 e3e0635b7c82
parent 10 38e8f01b347a
child 348 cbe401cf64dd
permissions -rw-r--r--
changed: #version_SVN

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

"{ NameSpace: SVN }"

Object subclass:#Command
	instanceVariableNames:'transcript'
	classVariableNames:''
	poolDictionaries:''
	category:'SVN-Private-Commands'
!


!Command class methodsFor:'instance creation'!

for: aSVNRepository

    ^self new

    "Created: / 15-03-2008 / 21:18:34 / janfrog"
    "Modified: / 15-03-2008 / 23:32:10 / janfrog"
!

new
    ^ self basicNew initialize.

    "Created: / 16-03-2008 / 07:45:22 / janfrog"
! !

!Command class methodsFor:'accessing'!

verbose

    ^UserPreferences current svnVerbose

    "Created: / 19-03-2008 / 12:29:47 / janfrog"
    "Modified: / 19-03-2009 / 14:00:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

verbose: aBoolean

    UserPreferences current svnVerbose: aBoolean

    "Created: / 19-03-2008 / 12:29:59 / janfrog"
    "Modified: / 19-03-2009 / 14:00:59 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!Command methodsFor:'accessing'!

transcript
    ^ transcript ? Transcript

    "Created: / 31-03-2008 / 15:37:39 / janfrog"
!

transcript:something
    transcript := something.

    "Created: / 31-03-2008 / 15:37:39 / janfrog"
! !

!Command methodsFor:'executing'!

execute


    ^self svnExecute

    "Modified: / 03-10-2008 / 17:25:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

svnStderrStream
    ^ (String new:64) writeStream

    "Created: / 16-03-2008 / 07:50:38 / janfrog"
!

svnStdoutStream
    ^ (String new:64) writeStream

    "Created: / 16-03-2008 / 07:50:17 / janfrog"
! !

!Command methodsFor:'executing - private'!

svnCmd
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility

    "Created: / 15-03-2008 / 21:03:26 / janfrog"
!

svnCmdArgumentsOn:argStream 
    "raise an error: must be redefined in concrete subclass(es)"
    
    ^ self subclassResponsibility

    "Created: / 15-03-2008 / 21:21:11 / janfrog"
!

svnCmdWorkdir
    "raise an error: must be redefined in concrete subclass(es)"

    ^ '.'

    "Created: / 15-03-2008 / 23:41:48 / janfrog"
!

svnExecute
    |svnStdoutStream svnStderrStream svnProcess|

    svnStdoutStream := self svnStdoutStream.
    svnStderrStream := self svnStderrStream.
    svnProcess := (self svnExternalProcess)
                stdout:svnStdoutStream;
                stderr:svnStderrStream.
    self class verbose ifTrue:[
        | ctx |
        ctx := thisContext.
        5 timesRepeat:[ctx := ctx sender].
        (self transcript)
            cr;
            show:'[SVN] ';
            showCR:svnProcess asShellCommandString;
            show:'      in ';
            showCR:self svnCmdWorkdir;
            show:'[SVN] #called from ';
            showCR:ctx printString;
            show:'[SVN] #called from ';
            showCR:ctx sender printString;
            show:'[SVN] #called from ';
            showCR:ctx sender sender printString
    ].
    svnProcess
        execute;
        waitFor.
    self class verbose ifTrue:[
        svnStdoutStream contents isEmpty not ifTrue:[
            svnStdoutStream contents asStringCollection do:[:line | 
                "self transcript show:'[SVN] '; show: line; cr"
            ]
        ].
        svnStderrStream contents isEmpty not ifTrue:[
            svnStderrStream contents asStringCollection do:[:line | 
                (self transcript)
                    show:(('[SVN] ' , line) asText colorizeAllWith:Color red);
                    cr
            ]
        ].
    ].
    ^ svnProcess exitValue isZero 
        ifTrue:
            [self svnProcessCommandOutput:svnStdoutStream contents readStream
                err:svnStderrStream contents readStream]
        ifFalse:
            [self svnProcessCommandError:svnStderrStream contents]

    "Modified: / 31-03-2008 / 15:39:40 / janfrog"
    "Created: / 03-10-2008 / 17:25:29 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 08-04-2009 / 22:18:39 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

svnExternalProcess
    |argStream|

    argStream := OrderedCollection new writeStream.
    self svnGlobalArgumentsOn:argStream.
    argStream nextPut:self svnCmd.
    self svnCmdArgumentsOn:argStream.
    ^ (OSProcess new)
        executable:self svnProgram;
        arguments:argStream contents;
        workdir:self svnCmdWorkdir;
        yourself

    "Modified: / 15-03-2008 / 23:41:26 / janfrog"
    "Created: / 03-10-2008 / 16:32:13 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

svnGlobalArgumentsOn: argStream

    argStream 
        nextPut:'--non-interactive'.

    "Created: / 03-10-2008 / 17:28:55 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

svnProcessCommandError: errorString

    ^(SVN::Error raiseErrorString: errorString)

    "Created: / 03-10-2008 / 16:33:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 03-10-2008 / 17:48:05 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

svnProcessCommandOutput:svnStdoutStream err:svnStderrStream 
    self subclassResponsibility

    "Created: / 03-10-2008 / 16:31:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

svnProgram
    ^ 'svn'
! !

!Command methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    "/ please change as required (and remove this comment)

    "/ super initialize.   -- commented since inherited method does nothing

    "Created: / 16-03-2008 / 07:45:22 / janfrog"
! !

!Command class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^'Id: SVN__Command.st 70 2009-04-16 12:47:44Z vranyj1 '
! !