SVN__CVSTask.st
author fm
Mon, 19 Oct 2009 14:21:44 +0200
changeset 390 8a91b2cebd5a
parent 326 1966f5dd62b4
child 492 74ff0960961c
permissions -rw-r--r--
*** empty log message ***

"{ Package: 'stx:libsvn' }"

"{ NameSpace: SVN }"

nil subclass:#CVSTask
	instanceVariableNames:'packageDir tmpDir cvsRoot transcript'
	classVariableNames:'CVSRoot'
	poolDictionaries:''
	category:'SVN-Tasks'
!


!CVSTask class methodsFor:'instance creation'!

new
    ^ self basicNew initialize.
! !

!CVSTask class methodsFor:'accessing'!

cvsRoot

    ^CVSRoot

    "
        self cvsRoot 
        self cvsRoot: '/home/janfrog/Projects/SmalltalkX/sandbox/cvs'     
    "

    "Created: / 25-05-2009 / 19:52:04 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 26-05-2009 / 18:26:31 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

cvsRoot: aString

    CVSRoot := aString

    "
        CVS2SVN_Convert cvsRoot: '/home/janfrog/Projects/SmalltalkX/sandbox/cvs'   
    "

    "Created: / 25-05-2009 / 19:51:49 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CVSTask class methodsFor:'execution'!

doFor:packages 
    self doFor:packages
        logOn:Filename defaultTempDirectoryName pathName 
                , Filename separatorString , 'convert.log'

    "Created: / 26-05-2009 / 18:20:25 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 28-05-2009 / 11:41:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doFor: pkgs logOn: log 
    | transcript  packages failed |

    packages := pkgs isString ifTrue: [ Array with: pkgs ] ifFalse: [ pkgs ].
    transcript := SplittingWriteStream 
                    on: Transcript
                    and: log asFilename writeStream.
    transcript showCR: 'Logging on ' , log asString.

    failed := false.
    
    packages do: 
        [:pkg|
        [self new package: pkg; transcript: transcript; do]
            on: Error do:
                [:ex|
                transcript showCR: 'ERROR: Synchronization of ' , pkg , ' failed!!'.
                ex suspendedContext fullPrintAllOn:transcript.
                failed := true]].
    failed ifTrue:
        [transcript 
            showCR:'Synchronization of one or more packages failed!!';
            showCR:'See the log for details'].

    transcript outStream2 close.

    "Created: / 26-05-2009 / 18:08:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 19-08-2009 / 12:39:35 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CVSTask methodsFor:'accessing'!

cvsRoot
    ^ cvsRoot
!

cvsRoot:aStringOrFilename
    cvsRoot := aStringOrFilename asFilename.

    "Modified: / 25-05-2009 / 19:54:38 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

obsoleteFileNames

    ^#(
       '.cvsignore'
    )

    "Created: / 30-05-2009 / 15:48:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 02-06-2009 / 13:38:33 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

package
    ^ package
!

package: aStringOrSymbol 
    package := aStringOrSymbol asSymbol.
    packageDir := (aStringOrSymbol asString copyReplaceAll: $: with: $/) 
                asSymbol.
    workingCopy := self svnWorkingCopy.

    "Modified: / 19-08-2009 / 11:26:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

svnWorkingCopyPath
    ^ (tmpDir construct: 'svn-working-copy') construct: (packageDir asFilename baseName)

    "Modified: / 19-08-2009 / 11:25:48 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

transcript
    ^ transcript
!

transcript:something
    transcript := something.
! !

!CVSTask methodsFor:'executing'!

doCleanup

    tmpDir recursiveRemove

    "Created: / 29-05-2009 / 17:17:20 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doFixPackageContentIn: dir

    self
       doRemoveObsoleteFilesIn: dir;
       doNormalizeClassContainerNamesIn: dir;
       doNormalizeEndOfLineIn: dir;
       doNormalizeVersionMethodIn: dir

    "Created: / 02-06-2009 / 17:31:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CVSTask methodsFor:'executing - helpers'!

doNormalizeClassContainerNamesIn: dir 
    | files |

    self notify: 'Normalizing class container names'.
    files := dir directoryContentsAsFilenamesMatching: '*.st'.
    files do: 
            [:file | 
            | change |

            change := (ChangeSet fromFile: file) first.
            change isClassDefinitionChange 
                ifTrue: 
                    [ | oldName  newName |

                    oldName := file baseName.
                    newName := (change className replaceAll: $: with: $_) , '.st'.
                    oldName ~= newName 
                        ifTrue: 
                            [ | sed |

                            self renameFile: (dir / oldName) to: (dir / newName).
                             "
                             Also, we have to update makefiles. Grrr, I hate this
                             build system.
                            "
                            sed := (OSProcess new)
                                        executable: '/bin/sed';
                                        workdir: dir;
                                        arguments: (Array 
                                                    with: '-i'
                                                    with: '-e'
                                                    with: ('"s/' , (oldName upTo: $.) , '/' , (newName upTo: $.) , '/g"')) 
                                                        , (dir 
                                                                directoryContentsMatching: #( 'Make.*' 'Makefile' 'makefile' '*.mak' 'abbrev.stc' ));
                                        stdout: transcript;
                                        stderr: transcript.
                            sed execute.
                            self assert: sed exitValue = 0
                                message: 'sed failed to finish properly. Check transcript'. ] ] ].

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

doNormalizeEndOfLineIn: dir 
    | files  sed |

    self notify: 'Normalizing end-of-lines'.
    files := dir directoryContentsAsFilenames select: [:e | e suffix = 'st' ].
    sed := (OSProcess new)
                executable: '/bin/sed';
                arguments: (Array 
                            with: '-i'
                            with: '-e'
                            with: 's/\r[^\n]/\n/g') , (files collect: [:e | e pathName ]);
                stdout: transcript;
                stderr: transcript.
    sed execute.
    self assert: sed exitValue = 0
        message: 'sed failed to finish properly. Check transcript'.

    "Created: / 29-05-2009 / 18:27:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 30-05-2009 / 16:06:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doNormalizeVersionMethodIn: dir

    self doNormalizeVersionMethodIn: dir doCopy: false

    "Created: / 29-05-2009 / 18:27:29 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 03-06-2009 / 11:22:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doNormalizeVersionMethodIn: dir doCopy: doCopy 
    | files  sed |

    self notify: 'Normalizing #version methods'.
    files := dir 
                directoryContentsAsFilenamesMatching: #( '*.st' 'Make.*' 'Makefile' 'makefile' '*.mak' '*.c' '*.cc' ).
    doCopy 
        ifTrue: 
            [ files do: [:f | f copyTo: (f pathName , '~') asFilename ].
            files := files collect: [:f | (f pathName , '~') asFilename ] ].
    sed := (OSProcess new)
                executable: '/bin/sed';
                arguments: (Array 
                            with: '-i'
                            with: '-e'
                            with: '"s/''\$Id.*\$''/''\$Id\$''/g"'
                            with: '-e'
                            with: '"s/''\$Header.*\$''/''\$Id\$''/g"') 
                                , (files collect: [:e | e pathName ]);
                stdout: transcript;
                stderr: transcript.
    sed execute.
    self assert: sed exitValue = 0
        message: 'sed failed to finish properly. Check transcript'.

    "Created: / 03-06-2009 / 11:26:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doRemoveDuplicateCommaVFilesInAtticIn:cvsDir 
    |cvsAtticDir cvsDirContents|

    cvsAtticDir := cvsDir construct:'Attic'.
    cvsDirContents := cvsDir directoryContents.
    cvsAtticDir exists ifTrue:[
        cvsAtticDir 
            directoryContentsAsFilenamesDo:[:atticFile | 
                (cvsDirContents includes:atticFile baseName) ifTrue:[
                    self info:'removing stale file ' , atticFile baseName , ' in Attic'.
                    atticFile remove
                    
                    "/cvsAtticDir remove.                    
                ]
            ]
    ].
    cvsDir 
        directoryContentsAsFilenamesDo:[:file | 
            (file isDirectory and:[ file baseName ~= 'Attic' ]) ifTrue:[
                self doRemoveDuplicateCommaVFilesInAtticIn:file
            ]
        ]

    "Created: / 25-05-2009 / 22:35:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 26-05-2009 / 18:27:06 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doRemoveObsoleteFilesIn: dir

    self notify: 'Removing obsolete files'.
    self removeFiles: self obsoleteFileNames.

    "Created: / 30-05-2009 / 15:43:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doSVNAddFilesFor: files 
    self notify: 'Adding files'.
    files isEmpty ifTrue: [ ^ self ].
    (AddCommand new)
        workingCopy: workingCopy;
        paths: files;
        execute

    "Created: / 02-06-2009 / 19:01:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 19-08-2009 / 11:26:57 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doSVNSetSvnEolStylePropertyFor: files 
    self notify: 'Setting svn:eol-style property to LF'.
    files isEmpty ifTrue: [ ^ self ].
    (PropsetCommand new)
        workingCopy: workingCopy;
        name: 'svn:eol-style';
        value: 'LF';
        paths: files;
        execute

    "Modified: / 19-08-2009 / 11:27:02 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doSVNSetSvnKeywordPropertyFor: files 
    self notify: 'Setting svn:keywords property to Id'.
    files isEmpty ifTrue: [ ^ self ].
    (PropsetCommand new)
        workingCopy: workingCopy;
        name: 'svn:keywords';
        value: 'Id';
        paths: files;
        execute

    "Modified: / 19-08-2009 / 11:27:05 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CVSTask methodsFor:'executing - private'!

doSVNCheckout
    self notify: 'Checking out'.
    workingCopy checkout: Revision head

    "Modified: / 19-08-2009 / 12:42:48 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

doSVNCommit
    self notify: 'Commiting'.
    (CommitCommand new)
        workingCopy: workingCopy;
        message: self svnCommitMessage;
        execute

    "Created: / 29-05-2009 / 18:13:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 19-08-2009 / 11:28:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CVSTask methodsFor:'initialization'!

initialize

    cvsRoot := self class cvsRoot asFilename.
    tmpDir := Filename newTemporaryDirectory.

    "Modified: / 29-05-2009 / 17:13:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CVSTask methodsFor:'passes'!

normalizeVersionMethod: files 
    | sed |

    sed := (OSProcess new)
                executable: '/bin/sed';
                arguments: (Array 
                            with: '-i'
                            with: '-e'
                            with: '"s/\^\ ?''$Id.*$''/\^''$' , 'Id$' , '''/g"'
                            with: '-e'
                            with: '"s/\^\ ?''\$Header.*\$''/\^ ''\$Id\$''/g"') 
                                , (files collect: [:e | e pathName ]);
                stdout: transcript;
                stderr: transcript.
    sed execute.
    self assert: sed exitValue = 0
        message: 'sed failed to finish properly. Check transcript'.

    "Modified: / 19-08-2009 / 11:02:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CVSTask methodsFor:'private'!

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

    ^ self subclassResponsibility
!

renameFile:arg1 to:arg2
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility
!

svnBranch

    ^Branch repository: self svnRepository path: self svnBranchPath

    "Created: / 19-08-2009 / 11:20:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

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

    ^ self subclassResponsibility

    "Created: / 19-08-2009 / 11:18:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

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

    ^ self subclassResponsibility
!

svnRepository

    ^Repository package: package url: self svnRepositoryUrl

    "Created: / 19-08-2009 / 11:12:25 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 19-08-2009 / 12:23:58 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

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

    ^ self subclassResponsibility
!

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

    ^WorkingCopy 
        branch: self svnBranch
        path: self svnWorkingCopyPath

    "Created: / 19-08-2009 / 11:23:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CVSTask class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^'§Id: SVN__CVSTask.st 110 2009-08-19 13:21:10Z vranyj1 §'
! !