*** empty log message ***
authorfm
Mon, 19 Oct 2009 14:52:48 +0200
changeset 492 74ff0960961c
parent 491 19c6e1b8dfff
child 493 256fe6b542c3
*** empty log message ***
SVN__AddCommand.st
SVN__BranchCommand.st
SVN__CVSTask.st
SVN__CheckoutCommand.st
SVN__CleanupCommand.st
SVN__CommitCommand.st
SVN__CommitTask.st
SVN__CommitTests.st
SVN__CopyCommand.st
SVN__DeleteCommand.st
SVN__FileoutLikeTask.st
SVN__InfoCommand.st
SVN__MoveCommand.st
SVN__PropsetCommand.st
SVN__RevertCommand.st
SVN__RevisionLogEntry.st
SVN__StatusCommand.st
SVN__TestCase.st
SVN__UpdateCommand.st
SVN__WCEntryInfo.st
--- a/SVN__AddCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__AddCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#AddCommand
+WCPathCommand subclass:#AddCommand
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
--- a/SVN__BranchCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__BranchCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#BranchCommand
+Command subclass:#BranchCommand
 	instanceVariableNames:'branch username password noAuthCache alreadyCleaned revision'
 	classVariableNames:''
 	poolDictionaries:''
@@ -42,22 +42,22 @@
 
 execute
     ^ [ super execute ] on:SVN::AuthorizationError
-        do:[:ex | 
+	do:[:ex |
     |credentials dialog|
 
     credentials := Credentials new username:OperatingSystem getLoginName.
     credentials := (dialog := CredentialsDialog new)
-                model:credentials;
-                subTitle:self url;
-                open.
-    credentials 
-        ifNil:[ ex pass ]
-        ifNotNil:[
-            username := credentials username.
-            password := credentials password.
-            noAuthCache := dialog savePassword not.
-            self execute
-        ]
+		model:credentials;
+		subTitle:self url;
+		open.
+    credentials
+	ifNil:[ ex pass ]
+	ifNotNil:[
+	    username := credentials username.
+	    password := credentials password.
+	    noAuthCache := dialog savePassword not.
+	    self execute
+	]
 ]
 
     "Created: / 03-10-2008 / 17:26:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -73,16 +73,16 @@
     "/argStream nextPut:'--config-dir'; nextPut:'/tmp/.svn'; nextPut:'--no-auth-cache'.
 
     username ifNotNil:
-        [argStream 
-            nextPut: '--username';
-            nextPut: username].
+	[argStream
+	    nextPut: '--username';
+	    nextPut: username].
     password ifNotNil:
-        [argStream 
-            nextPut: '--password';
-            nextPut: password].
+	[argStream
+	    nextPut: '--password';
+	    nextPut: password].
     noAuthCache == true ifTrue:
-        [argStream
-            nextPutAll:'--no-auth-cache']
+	[argStream
+	    nextPutAll:'--no-auth-cache']
 
     "Created: / 03-10-2008 / 17:31:04 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
--- a/SVN__CVSTask.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__CVSTask.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#CVSTask
+Task subclass:#CVSTask
 	instanceVariableNames:'packageDir tmpDir cvsRoot transcript'
 	classVariableNames:'CVSRoot'
 	poolDictionaries:''
@@ -23,8 +23,8 @@
     ^CVSRoot
 
     "
-        self cvsRoot 
-        self cvsRoot: '/home/janfrog/Projects/SmalltalkX/sandbox/cvs'     
+	self cvsRoot
+	self cvsRoot: '/home/janfrog/Projects/SmalltalkX/sandbox/cvs'
     "
 
     "Created: / 25-05-2009 / 19:52:04 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -36,7 +36,7 @@
     CVSRoot := aString
 
     "
-        CVS2SVN_Convert cvsRoot: '/home/janfrog/Projects/SmalltalkX/sandbox/cvs'   
+	CVS2SVN_Convert cvsRoot: '/home/janfrog/Projects/SmalltalkX/sandbox/cvs'
     "
 
     "Created: / 25-05-2009 / 19:51:49 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -44,38 +44,38 @@
 
 !CVSTask class methodsFor:'execution'!
 
-doFor:packages 
+doFor:packages
     self doFor:packages
-        logOn:Filename defaultTempDirectoryName pathName 
-                , Filename separatorString , 'convert.log'
+	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 
+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 := 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]].
+
+    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
+	    showCR:'Synchronization of one or more packages failed!!';
+	    showCR:'See the log for details'].
 
     transcript outStream2 close.
 
@@ -109,10 +109,10 @@
     ^ package
 !
 
-package: aStringOrSymbol 
+package: aStringOrSymbol
     package := aStringOrSymbol asSymbol.
-    packageDir := (aStringOrSymbol asString copyReplaceAll: $: with: $/) 
-                asSymbol.
+    packageDir := (aStringOrSymbol asString copyReplaceAll: $: with: $/)
+		asSymbol.
     workingCopy := self svnWorkingCopy.
 
     "Modified: / 19-08-2009 / 11:26:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -154,66 +154,66 @@
 
 !CVSTask methodsFor:'executing - helpers'!
 
-doNormalizeClassContainerNamesIn: dir 
+doNormalizeClassContainerNamesIn: dir
     | files |
 
     self notify: 'Normalizing class container names'.
     files := dir directoryContentsAsFilenamesMatching: '*.st'.
-    files do: 
-            [:file | 
-            | change |
+    files do:
+	    [:file |
+	    | change |
 
-            change := (ChangeSet fromFile: file) first.
-            change isClassDefinitionChange 
-                ifTrue: 
-                    [ | oldName  newName |
+	    change := (ChangeSet fromFile: file) first.
+	    change isClassDefinitionChange
+		ifTrue:
+		    [ | oldName  newName |
 
-                    oldName := file baseName.
-                    newName := (change className replaceAll: $: with: $_) , '.st'.
-                    oldName ~= newName 
-                        ifTrue: 
-                            [ | sed |
+		    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'. ] ] ].
+			    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 
+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.
+		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'.
+	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>"
@@ -227,56 +227,56 @@
     "Modified: / 03-06-2009 / 11:22:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
-doNormalizeVersionMethodIn: dir doCopy: doCopy 
+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 ] ].
+    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.
+		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'.
+	message: 'sed failed to finish properly. Check transcript'.
 
     "Created: / 03-06-2009 / 11:26:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
-doRemoveDuplicateCommaVFilesInAtticIn:cvsDir 
+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.                    
-                ]
-            ]
+	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
-            ]
-        ]
+    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>"
@@ -290,40 +290,40 @@
     "Created: / 30-05-2009 / 15:43:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
-doSVNAddFilesFor: files 
+doSVNAddFilesFor: files
     self notify: 'Adding files'.
     files isEmpty ifTrue: [ ^ self ].
     (AddCommand new)
-        workingCopy: workingCopy;
-        paths: files;
-        execute
+	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 
+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
+	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 
+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
+	workingCopy: workingCopy;
+	name: 'svn:keywords';
+	value: 'Id';
+	paths: files;
+	execute
 
     "Modified: / 19-08-2009 / 11:27:05 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
@@ -340,9 +340,9 @@
 doSVNCommit
     self notify: 'Commiting'.
     (CommitCommand new)
-        workingCopy: workingCopy;
-        message: self svnCommitMessage;
-        execute
+	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>"
@@ -360,23 +360,23 @@
 
 !CVSTask methodsFor:'passes'!
 
-normalizeVersionMethod: files 
+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.
+		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'.
+	message: 'sed failed to finish properly. Check transcript'.
 
     "Modified: / 19-08-2009 / 11:02:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
@@ -433,9 +433,9 @@
 svnWorkingCopy
     "raise an error: must be redefined in concrete subclass(es)"
 
-    ^WorkingCopy 
-        branch: self svnBranch
-        path: self svnWorkingCopyPath
+    ^WorkingCopy
+	branch: self svnBranch
+	path: self svnWorkingCopyPath
 
     "Created: / 19-08-2009 / 11:23:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
--- a/SVN__CheckoutCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__CheckoutCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#CheckoutCommand
+UpdateLikeCommand subclass:#CheckoutCommand
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -20,13 +20,13 @@
     "Created: / 15-03-2008 / 23:48:44 / janfrog"
 !
 
-svnCmdArgumentsOn: arg 
+svnCmdArgumentsOn: arg
     "raise an error: must be redefined in concrete subclass(es)"
-    
+
     super svnCmdArgumentsOn: arg.
     arg
-        nextPut: self url asString;
-        nextPut: '.'
+	nextPut: self url asString;
+	nextPut: '.'
 
     "Created: / 15-03-2008 / 23:48:44 / janfrog"
     "Modified: / 19-03-2008 / 12:44:01 / janfrog"
--- a/SVN__CleanupCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__CleanupCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#CleanupCommand
+WCCommand subclass:#CleanupCommand
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
--- a/SVN__CommitCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__CommitCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#CommitCommand
+WCPathCommand subclass:#CommitCommand
 	instanceVariableNames:'message url username password noAuthCache'
 	classVariableNames:''
 	poolDictionaries:''
@@ -41,22 +41,22 @@
 
 execute
     ^ [ super execute ] on:SVN::AuthorizationError
-        do:[:ex | 
+	do:[:ex |
     |credentials dialog|
 
     credentials := Credentials new username:OperatingSystem getLoginName.
     credentials := (dialog := CredentialsDialog new)
-                model:credentials;
-                subtitle:self url;
-                open.
-    credentials 
-        ifNil:[ ex pass ]
-        ifNotNil:[
-            username := credentials username.
-            password := credentials password.
-            noAuthCache := dialog savePassword not.
-            self execute
-        ]
+		model:credentials;
+		subtitle:self url;
+		open.
+    credentials
+	ifNil:[ ex pass ]
+	ifNotNil:[
+	    username := credentials username.
+	    password := credentials password.
+	    noAuthCache := dialog savePassword not.
+	    self execute
+	]
 ]
 
     "Created: / 03-10-2008 / 18:22:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -73,7 +73,7 @@
     "Created: / 16-03-2008 / 07:47:00 / janfrog"
 !
 
-svnCmdArgumentsOn:arg 
+svnCmdArgumentsOn:arg
 
     arg nextPut:'--message'; nextPut: (message ? '').
     super svnCmdArgumentsOn:arg
@@ -89,23 +89,23 @@
     "/argStream nextPut:'--config-dir'; nextPut:'/tmp/.svn'; nextPut:'--no-auth-cache'.
 
     username ifNotNil:
-        [argStream 
-            nextPut: '--username';
-            nextPut: username].
+	[argStream
+	    nextPut: '--username';
+	    nextPut: username].
     password ifNotNil:
-        [argStream 
-            nextPut: '--password';
-            nextPut: password].
+	[argStream
+	    nextPut: '--password';
+	    nextPut: password].
     noAuthCache == true ifTrue:
-        [argStream
-            nextPutAll:'--no-auth-cache']
+	[argStream
+	    nextPutAll:'--no-auth-cache']
 
     "Created: / 31-10-2008 / 09:30:54 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
-svnProcessCommandOutput:arg1 err:arg2 
+svnProcessCommandOutput:arg1 err:arg2
     "Superclass says that I am responsible to implement this method"
-    
+
     ^ arg1 contents
 
     "Created: / 03-10-2008 / 16:31:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
--- a/SVN__CommitTask.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__CommitTask.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#CommitTask
+FileoutLikeTask subclass:#CommitTask
 	instanceVariableNames:'message'
 	classVariableNames:''
 	poolDictionaries:''
@@ -15,13 +15,13 @@
 buildSupportFilesFor: pkgDef
 
     | common |
-    common := #('abbrev.stc' 'Make.proto' 'Make.spec').    
+    common := #('abbrev.stc' 'Make.proto' 'Make.spec').
     ^pkgDef isApplicationDefinition
-        ifTrue:[common]
-        ifFalse:[common copyWith: 'libInit.cc']
-        
+	ifTrue:[common]
+	ifFalse:[common copyWith: 'libInit.cc']
+
     "
-        SVN::CommitTask basicNew buildSupportFilesFor: stx_goodies_libsvn
+	SVN::CommitTask basicNew buildSupportFilesFor: stx_goodies_libsvn
     "
 
     "Created: / 20-06-2009 / 12:03:51 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -40,8 +40,8 @@
 do
 
     self
-        doUpdateWorkingCopy;
-        doCommit
+	doUpdateWorkingCopy;
+	doCommit
 
     "Created: / 23-03-2009 / 11:15:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 17-06-2009 / 10:16:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -50,29 +50,29 @@
 doCommit
     | containers  commitInfo |
 
-    self do: 
-            [ SVN::ActivityNotification notify: 'Commiting ' , self package.
-            containers := self isSelectiveFileoutTask 
-                        ifTrue: [ self containersToFileOut ]
-                        ifFalse: [ #() ].
-            self synchronized: 
-                    [ commitInfo := (CommitCommand new)
-                                workingCopy: self workingCopy;
-                                message: message ? '<no message>';
-                                paths: containers;
-                                execute.
-                     "Update the working copy. We need svn info
-                     to report commited revision"
-                    (UpdateCommand new)
-                        workingCopy: self workingCopy;
-                        execute ].
-            self doCompileSvnRevisionNrMethod: true.
-            SVN::ActivityNotification notify: 'Shrinking changes'.
-            (ChangeSet current)
-                condenseChangesForPackage2: self package;
-                condenseChangesForExtensionsInPackage: self package;
-                flushChangedClassesCache;
-                yourself. ].
+    self do:
+	    [ SVN::ActivityNotification notify: 'Commiting ' , self package.
+	    containers := self isSelectiveFileoutTask
+			ifTrue: [ self containersToFileOut ]
+			ifFalse: [ #() ].
+	    self synchronized:
+		    [ commitInfo := (CommitCommand new)
+				workingCopy: self workingCopy;
+				message: message ? '<no message>';
+				paths: containers;
+				execute.
+		     "Update the working copy. We need svn info
+		     to report commited revision"
+		    (UpdateCommand new)
+			workingCopy: self workingCopy;
+			execute ].
+	    self doCompileSvnRevisionNrMethod: true.
+	    SVN::ActivityNotification notify: 'Shrinking changes'.
+	    (ChangeSet current)
+		condenseChangesForPackage2: self package;
+		condenseChangesForExtensionsInPackage: self package;
+		flushChangedClassesCache;
+		yourself. ].
     self workingCopy commited.
     ^ commitInfo
 
@@ -83,8 +83,8 @@
 doUpdateWorkingCopy
 
     self do:[
-        self workingCopy ensureIsValid.
-        self doFileOutAll
+	self workingCopy ensureIsValid.
+	self doFileOutAll
     ]
 
     "Created: / 11-04-2008 / 09:19:27 / Jan Vrany <vranyj1@fel.cvut.cz>"
--- a/SVN__CommitTests.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__CommitTests.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#CommitTests
+TestCase subclass:#CommitTests
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -16,9 +16,9 @@
 
     super setUp.
     Class withoutUpdatingChangesDo:
-        [self source_stx_goodies_libsvn_CommitTests_st readStream fileIn.
-        self source_SVN__CommitTestsMockA_st readStream fileIn.
-        self source_SVN__CommitTestsMockB_st readStream fileIn]
+	[self source_stx_goodies_libsvn_CommitTests_st readStream fileIn.
+	self source_SVN__CommitTestsMockA_st readStream fileIn.
+	self source_SVN__CommitTestsMockB_st readStream fileIn]
 
     "Created: / 19-08-2009 / 14:59:20 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
@@ -27,11 +27,11 @@
 
 source_SVN__CommitTestsMockA_st
 
-        "
-        SVN::CommitTestsMockA fileOutAsMethodIn: SVN::CommitTests selector: #'source_SVN__CommitTestsMockA_st' category: 'sources'
+	"
+	SVN::CommitTestsMockA fileOutAsMethodIn: SVN::CommitTests selector: #'source_SVN__CommitTestsMockA_st' category: 'sources'
 
-        SVN::CommitTests new source_SVN__CommitTestsMockA_st
-        "
+	SVN::CommitTests new source_SVN__CommitTestsMockA_st
+	"
 
 ^'''From Smalltalk/X, Version:5.4.4 on 08-04-2009 at 09:23:01 PM''                  !!
 
@@ -40,10 +40,10 @@
 "{ NameSpace: SVN }"
 
 Object subclass:#CommitTestsMockA
-        instanceVariableNames:''''
-        classVariableNames:''''
-        poolDictionaries:''''
-        category:''SVN-Tests-Mocks''
+	instanceVariableNames:''''
+	classVariableNames:''''
+	poolDictionaries:''''
+	category:''SVN-Tests-Mocks''
 !!
 
 '
@@ -53,21 +53,21 @@
 
 source_SVN__CommitTestsMockB_st
 
-        "
-        SVN::CommitTestsMockA fileOutAsMethodIn: SVN::CommitTests selector: #'source_SVN__CommitTestsMockA_st' category: 'sources'
+	"
+	SVN::CommitTestsMockA fileOutAsMethodIn: SVN::CommitTests selector: #'source_SVN__CommitTestsMockA_st' category: 'sources'
 
-        SVN::CommitTests new source_SVN__CommitTestsMockA_st
-        "
+	SVN::CommitTests new source_SVN__CommitTestsMockA_st
+	"
 
 ^'"{ Package: ''stx:goodies/libsvn_CommitTests'' }"
 
 "{ NameSpace: SVN }"
 
 Object subclass:#CommitTestsMockB
-        instanceVariableNames:''''
-        classVariableNames:''''
-        poolDictionaries:''''
-        category:''SVN-Tests-Mocks''
+	instanceVariableNames:''''
+	classVariableNames:''''
+	poolDictionaries:''''
+	category:''SVN-Tests-Mocks''
 !!
 
 '
@@ -78,28 +78,28 @@
 
 source_stx_goodies_libsvn_CommitTests_st
 
-        "
-        stx_goodies_libsvnCommitTests fileOutAsMethodIn: SVN::CommitTests selector: #'source_stx_goodies_libsvnCommitTests_st' category: 'sources'
+	"
+	stx_goodies_libsvnCommitTests fileOutAsMethodIn: SVN::CommitTests selector: #'source_stx_goodies_libsvnCommitTests_st' category: 'sources'
 
-        SVN::CommitTests new source_stx_goodies_libsvnCommitTests_st
-        "
+	SVN::CommitTests new source_stx_goodies_libsvnCommitTests_st
+	"
 
 ^'''From Smalltalk/X, Version:5.4.4 on 08-04-2009 at 09:23:54 PM''                  !!
 
 "{ Package: ''stx:goodies/libsvn_CommitTests'' }"
 
 LibraryDefinition subclass:#stx_goodies_libsvn_CommitTests
-        instanceVariableNames:''''
-        classVariableNames:''''
-        poolDictionaries:''''
-        category:''* Projects & Packages *''
+	instanceVariableNames:''''
+	classVariableNames:''''
+	poolDictionaries:''''
+	category:''* Projects & Packages *''
 !!
 
 !!stx_goodies_libsvn_CommitTests class methodsFor:''description''!!
 
 preRequisites
     ^ #(
-        #''stx:libbasic''    "LibraryDefinition - superclass of stx_goodies_libsvnCommitTests "
+	#''stx:libbasic''    "LibraryDefinition - superclass of stx_goodies_libsvnCommitTests "
     )
 !! !!
 
@@ -107,10 +107,10 @@
 
 classNamesAndAttributes
     ^ #(
-        "<className> or (<className> attributes...) in load order"
-        #''SVN::CommitTestsMockA''
-        #''SVN::CommitTestsMockB''
-        #''stx_goodies_libsvn_CommitTests''
+	"<className> or (<className> attributes...) in load order"
+	#''SVN::CommitTestsMockA''
+	#''SVN::CommitTestsMockB''
+	#''stx_goodies_libsvn_CommitTests''
     )
 !!
 
@@ -159,16 +159,16 @@
 
 sources
 
-    ^super sources , 
+    ^super sources ,
     #(
-        (dir  'trunk')
-        (file 'trunk/SVN__CommitTestsMockA.st'          source_SVN__CommitTestsMockA_st)
-        (file 'trunk/SVN__CommitTestsMockB.st'          source_SVN__CommitTestsMockB_st)
-        (file 'trunk/stx_goodies_libsvn_CommitTests.st'  source_stx_goodies_libsvn_CommitTests_st)
+	(dir  'trunk')
+	(file 'trunk/SVN__CommitTestsMockA.st'          source_SVN__CommitTestsMockA_st)
+	(file 'trunk/SVN__CommitTestsMockB.st'          source_SVN__CommitTestsMockB_st)
+	(file 'trunk/stx_goodies_libsvn_CommitTests.st'  source_stx_goodies_libsvn_CommitTests_st)
 
-        (dir  'branches')
+	(dir  'branches')
 
-        (dir  'tags')
+	(dir  'tags')
     )
 
     "Created: / 08-04-2009 / 21:25:37 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -180,17 +180,17 @@
 test_01_simple
 
     "
-        Tests the simpliest commit
+	Tests the simpliest commit
     "
 
     Class packageQuerySignal answer: self package do:
-        [SVN::CommitTestsMockA compile: 'r1 ^''Revision 1''' classified: 'methods - r1'].
+	[SVN::CommitTestsMockA compile: 'r1 ^''Revision 1''' classified: 'methods - r1'].
 
     wc commit:'CommitTests>>test_01 commit'.
 
     self assert:
-        (wc branch cat: 'SVN__CommitTestsMockA.st')
-            = (String streamContents:[:s| SVN::CommitTestsMockA fileOutOn: s withTimeStamp: false]).
+	(wc branch cat: 'SVN__CommitTestsMockA.st')
+	    = (String streamContents:[:s| SVN::CommitTestsMockA fileOutOn: s withTimeStamp: false]).
 
     "Created: / 12-06-2009 / 21:46:04 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 19-08-2009 / 14:57:46 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -203,7 +203,7 @@
     self assert:(Smalltalk at: #'SVN::CommitTestsMockA' ifAbsent:[nil]) notNil.
 
     Class packageQuerySignal answer: self package do:
-        [SVN::CommitTestsMockA compile: 'r1 ^''Revision 1''' classified: 'methods - r1'].
+	[SVN::CommitTestsMockA compile: 'r1 ^''Revision 1''' classified: 'methods - r1'].
 
 
     w := CommitWizard new.
@@ -225,7 +225,7 @@
 
     self assert: (repositoryCode = imageCode).
     "
-        DiffTextView openOn: repositoryCode and: imageCode
+	DiffTextView openOn: repositoryCode and: imageCode
     "
 
     "Created: / 12-06-2009 / 21:46:11 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -235,30 +235,30 @@
 test_02_selective_commit
 
     "
-        Selective class commit test
+	Selective class commit test
     "
 
     self assert:(Smalltalk at: #'SVN::CommitTestsMockA' ifAbsent:[nil]) notNil.
     self assert:(Smalltalk at: #'SVN::CommitTestsMockB' ifAbsent:[nil]) notNil.
-    
-    Class packageQuerySignal answer: self package do:
-        [SVN::CommitTestsMockA compile: 'r1 ^''Revision 1''' classified: 'methods - r1'].
 
     Class packageQuerySignal answer: self package do:
-        [SVN::CommitTestsMockB compile: 'r1 ^''Revision 1''' classified: 'methods - r1'].
+	[SVN::CommitTestsMockA compile: 'r1 ^''Revision 1''' classified: 'methods - r1'].
+
+    Class packageQuerySignal answer: self package do:
+	[SVN::CommitTestsMockB compile: 'r1 ^''Revision 1''' classified: 'methods - r1'].
 
     wc commitTask
-        classes: (Array with: SVN::CommitTestsMockA);
-        message: 'CommitTests>>test_03 commit';
-        do.
+	classes: (Array with: SVN::CommitTestsMockA);
+	message: 'CommitTests>>test_03 commit';
+	do.
 
     self assert:
-        (wc branch cat: 'SVN__CommitTestsMockA.st')
-            = (String streamContents:[:s| SVN::CommitTestsMockA fileOutOn: s withTimeStamp: false]).
+	(wc branch cat: 'SVN__CommitTestsMockA.st')
+	    = (String streamContents:[:s| SVN::CommitTestsMockA fileOutOn: s withTimeStamp: false]).
 
     self assert:
-        (wc branch cat: 'SVN__CommitTestsMockB.st')
-            = self source_SVN__CommitTestsMockB_st.
+	(wc branch cat: 'SVN__CommitTestsMockB.st')
+	    = self source_SVN__CommitTestsMockB_st.
 
     "Created: / 12-06-2009 / 21:46:25 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 19-08-2009 / 14:57:54 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -267,7 +267,7 @@
 test_03_class_remove
 
     "
-        Tests class remove
+	Tests class remove
     "
 
     self assert:(Smalltalk at: #'SVN::CommitTestsMockA' ifAbsent:[nil]) notNil.
@@ -276,8 +276,8 @@
     Smalltalk removeClass: SVN::CommitTestsMockB.
 
     wc commitTask
-        message: 'CommitTests>>test_03 commit';
-        do.
+	message: 'CommitTests>>test_03 commit';
+	do.
     self assert: (wc branch list size = (2 + 4)"Make.spec, Make.proto, abbrev.stc, libInit.cc")
 
     "Created: / 12-06-2009 / 21:52:09 / Jan Vrany <vranyj1@fel.cvut.cz>"
--- a/SVN__CopyCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__CopyCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#CopyCommand
+WCCommand subclass:#CopyCommand
 	instanceVariableNames:'src dst'
 	classVariableNames:''
 	poolDictionaries:''
@@ -46,13 +46,13 @@
     "Created: / 16-03-2008 / 10:15:18 / janfrog"
 !
 
-svnCmdArgumentsOn:arg 
+svnCmdArgumentsOn:arg
     "raise an error: must be redefined in concrete subclass(es)"
 
     super svnCmdArgumentsOn:arg.
-    arg 
-        nextPut: src;
-        nextPut: dst
+    arg
+	nextPut: src;
+	nextPut: dst
 
     "Created: / 16-03-2008 / 10:15:18 / janfrog"
 ! !
--- a/SVN__DeleteCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__DeleteCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#DeleteCommand
+WCPathCommand subclass:#DeleteCommand
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -20,12 +20,12 @@
     "Created: / 16-03-2008 / 10:14:04 / janfrog"
 !
 
-svnCmdArgumentsOn:arg 
+svnCmdArgumentsOn:arg
     "raise an error: must be redefined in concrete subclass(es)"
 
     super svnCmdArgumentsOn:arg.
-    arg 
-        nextPut:'--force'
+    arg
+	nextPut:'--force'
 
     "Created: / 19-04-2008 / 13:09:39 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
--- a/SVN__FileoutLikeTask.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__FileoutLikeTask.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#FileoutLikeTask
+Task subclass:#FileoutLikeTask
 	instanceVariableNames:'packageClassesChanged packageExtensionsChanged extensionMethods'
 	classVariableNames:''
 	poolDictionaries:''
@@ -29,32 +29,32 @@
     | filesToAdd  containers |
 
     SVN::ActivityNotification notify: 'Adding new containers'.
-    containers := self isSelectiveFileoutTask 
-                ifTrue: [ #() ]
-                ifFalse: [ self containersToFileOut ].
+    containers := self isSelectiveFileoutTask
+		ifTrue: [ #() ]
+		ifFalse: [ self containersToFileOut ].
     filesToAdd := ((StatusCommand new)
-                workingCopy: self workingCopy;
-                paths: containers;
-                execute) select: [:wcEntry | wcEntry status isUnversioned ]
-                    thenCollect: [:wcEntry | wcEntry path ].
-    filesToAdd isEmpty 
-        ifFalse: 
-            [ (AddCommand new)
-                workingCopy: self workingCopy;
-                paths: filesToAdd;
-                execute.
-            (PropsetCommand new)
-                workingCopy: self workingCopy;
-                name: 'svn:keywords';
-                value: 'Id';
-                paths: filesToAdd;
-                execute.
-            (PropsetCommand new)
-                workingCopy: self workingCopy;
-                name: 'svn:eol-style';
-                value: 'LF';
-                paths: filesToAdd;
-                execute ]
+		workingCopy: self workingCopy;
+		paths: containers;
+		execute) select: [:wcEntry | wcEntry status isUnversioned ]
+		    thenCollect: [:wcEntry | wcEntry path ].
+    filesToAdd isEmpty
+	ifFalse:
+	    [ (AddCommand new)
+		workingCopy: self workingCopy;
+		paths: filesToAdd;
+		execute.
+	    (PropsetCommand new)
+		workingCopy: self workingCopy;
+		name: 'svn:keywords';
+		value: 'Id';
+		paths: filesToAdd;
+		execute.
+	    (PropsetCommand new)
+		workingCopy: self workingCopy;
+		name: 'svn:eol-style';
+		value: 'LF';
+		paths: filesToAdd;
+		execute ]
 
     "Created: / 11-04-2008 / 10:58:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 19-08-2009 / 14:00:26 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -67,18 +67,18 @@
 
     SVN::ActivityNotification notify: 'Compiling #version methods...'.
     klasses := self classesToFileOut asArray.
-    klasses withIndexDo: 
-            [:cls :index | 
-            | metaCls |
+    klasses withIndexDo:
+	    [:cls :index |
+	    | metaCls |
 
-            metaCls := cls theMetaclass.
-            (metaCls includesSelector: versionMethodName) 
-                ifFalse: 
-                    [ metaCls compile: (metaCls versionMethodTemplateForSourceCodeManager:SVNSourceCodeManager) classified: 'documentation'.
-                    (metaCls compiledMethodAt: versionMethodName) setPackage: self package asSymbol ].
-            SVN::ProgressNotification 
-                notify: ('Compiling %1 (%2)' bindWith:versionMethodName with:cls nameWithoutPrefix)
-                progress: (klasses size / 100) * index. ]
+	    metaCls := cls theMetaclass.
+	    (metaCls includesSelector: versionMethodName)
+		ifFalse:
+		    [ metaCls compile: (metaCls versionMethodTemplateForSourceCodeManager:SVNSourceCodeManager) classified: 'documentation'.
+		    (metaCls compiledMethodAt: versionMethodName) setPackage: self package asSymbol ].
+	    SVN::ProgressNotification
+		notify: ('Compiling %1 (%2)' bindWith:versionMethodName with:cls nameWithoutPrefix)
+		progress: (klasses size / 100) * index. ]
 
     "Created: / 28-05-2008 / 07:43:43 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 16-08-2009 / 12:59:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -87,15 +87,15 @@
 doFileOutAll
 
     self
-        doInitStateVariables;
-        doUpdateProjectDefinition;
-        doUpdateBuildSupportFiles;
-        doCompileVersionMethods;
-        doCompileSvnRevisionNrMethod:false;
-        doFileOutPackageClasses;
-        doFileOutPackageExtensions;
-        doAddNewContainers;
-        doRemoveOldContainers.
+	doInitStateVariables;
+	doUpdateProjectDefinition;
+	doUpdateBuildSupportFiles;
+	doCompileVersionMethods;
+	doCompileSvnRevisionNrMethod:false;
+	doFileOutPackageClasses;
+	doFileOutPackageExtensions;
+	doAddNewContainers;
+	doRemoveOldContainers.
 
     "Created: / 17-08-2009 / 18:28:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
@@ -105,17 +105,17 @@
 
     ActivityNotification notify: 'Filing out package classes'.
     klasses := self classesToFileOut asArray.
-    klasses withIndexDo: 
-            [:cls :index | 
-            | clsStream |
+    klasses withIndexDo:
+	    [:cls :index |
+	    | clsStream |
 
-            SVN::ProgressNotification notify: 'Filing out ' , cls nameWithoutPrefix
-                progress: (100 / klasses size) * index.
-            (self shouldFileOutClass: cls) 
-                ifTrue: 
-                    [ 
-                    [ clsStream := self workingCopy containersWriteStreamForClass: cls.
-                    self workingCopy fileOutClass: cls on: clsStream ] ensure: [ clsStream ifNotNil: [ clsStream close ] ] ] ]
+	    SVN::ProgressNotification notify: 'Filing out ' , cls nameWithoutPrefix
+		progress: (100 / klasses size) * index.
+	    (self shouldFileOutClass: cls)
+		ifTrue:
+		    [
+		    [ clsStream := self workingCopy containersWriteStreamForClass: cls.
+		    self workingCopy fileOutClass: cls on: clsStream ] ensure: [ clsStream ifNotNil: [ clsStream close ] ] ] ]
 
     "Created: / 11-04-2008 / 10:58:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 19-08-2009 / 13:44:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -127,8 +127,8 @@
     self extensionMethodsToFileOut isEmpty ifTrue: [ ^ self ].
     SVN::ActivityNotification notify: 'Filing out extension methods'.
     extensionsStream := self workingCopy containerWriteStreamForExtensions.
-    [ self workingCopy fileOutExtensionsOn: extensionsStream ] 
-        ensure: [ extensionsStream close ]
+    [ self workingCopy fileOutExtensionsOn: extensionsStream ]
+	ensure: [ extensionsStream close ]
 
     "Modified: / 07-04-2008 / 08:37:25 / janfrog"
     "Created: / 11-04-2008 / 10:58:36 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -151,12 +151,12 @@
     containers := self workingCopy containers.
     containersToKeep := self workingCopy containersToKeep.
     containersToDelete := containers \ containersToKeep.
-    containersToDelete isEmpty 
-        ifFalse: 
-            [ (DeleteCommand new)
-                workingCopy: self workingCopy;
-                paths: containersToDelete;
-                execute ].
+    containersToDelete isEmpty
+	ifFalse:
+	    [ (DeleteCommand new)
+		workingCopy: self workingCopy;
+		paths: containersToDelete;
+		execute ].
 
     "Created: / 11-04-2008 / 11:00:27 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 19-08-2009 / 15:03:51 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -168,13 +168,13 @@
     SVN::ActivityNotification notify:'Updating build files'.
     pkgDef := self workingCopy packageDefinition.
     (self buildSupportFilesFor: pkgDef) do:
-        [:supportFileName| |supportFile stream|
-        supportFile := workingCopy path / supportFileName.
-        (packageClassesChanged or:[supportFile exists not]) ifTrue:
-            [SVN::ActivityNotification notify:'Updating ', supportFileName.
-            [stream :=  supportFile writeStream.
-            stream nextPutAll:(pkgDef generateFile:supportFileName)]
-                ensure:[ stream ifNotNil:[ stream close ]]]].
+	[:supportFileName| |supportFile stream|
+	supportFile := workingCopy path / supportFileName.
+	(packageClassesChanged or:[supportFile exists not]) ifTrue:
+	    [SVN::ActivityNotification notify:'Updating ', supportFileName.
+	    [stream :=  supportFile writeStream.
+	    stream nextPutAll:(pkgDef generateFile:supportFileName)]
+		ensure:[ stream ifNotNil:[ stream close ]]]].
 
     "Created: / 20-06-2009 / 16:01:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 21-06-2009 / 15:18:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -186,19 +186,19 @@
     (packageClassesChanged | packageExtensionsChanged) ifFalse:[^self].
 
     SVN::ActivityNotification notify:'Updating project definition'.
-    prjClass := Smalltalk 
-                at:(ProjectDefinition initialClassNameForDefinitionOf:self package) 
-                        asSymbol.
+    prjClass := Smalltalk
+		at:(ProjectDefinition initialClassNameForDefinitionOf:self package)
+			asSymbol.
     prjClass ifNotNil:
-        [Class packageQuerySignal 
-            answer:prjClass package
-            do:
-                [prjClass theNonMetaclass 
-                    forEachContentsMethodsCodeToCompileDo:
-                        [:code :category | 
-                        prjClass theMetaclass 
-                            compile:code classified:category]
-                            ignoreOldDefinition:true]]
+	[Class packageQuerySignal
+	    answer:prjClass package
+	    do:
+		[prjClass theNonMetaclass
+		    forEachContentsMethodsCodeToCompileDo:
+			[:code :category |
+			prjClass theMetaclass
+			    compile:code classified:category]
+			    ignoreOldDefinition:true]]
 
     "Created: / 11-04-2008 / 11:01:06 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 13-08-2009 / 09:13:14 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -207,9 +207,9 @@
 !FileoutLikeTask methodsFor:'private'!
 
 classesToFileOut
-    ^ self workingCopy packageClassesFiltered: 
-            [:class | 
-            class isLoaded and: [ classes isNil or: [ classes includes: class ] ] ]
+    ^ self workingCopy packageClassesFiltered:
+	    [:class |
+	    class isLoaded and: [ classes isNil or: [ classes includes: class ] ] ]
 
     "Created: / 23-03-2009 / 12:08:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 11-06-2009 / 18:17:38 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -218,43 +218,43 @@
 containersToFileOut
     | containers |
 
-    containers := self classesToFileOut 
-                collect: [:class | self repository containerNameForClass: class ].
-    self extensionMethodsToFileOut isEmpty 
-        ifFalse: [ containers add: self repository containerNameForExtensions ].
+    containers := self classesToFileOut
+		collect: [:class | self repository containerNameForClass: class ].
+    self extensionMethodsToFileOut isEmpty
+	ifFalse: [ containers add: self repository containerNameForExtensions ].
     ^ containers
 
     "Created: / 14-05-2009 / 11:35:05 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
 extensionMethodsToFileOut
-    ^ self workingCopy packageExtensionsFiltered: 
-            [:mth | 
-            extensionMethods isNil or: [ extensionMethods includes: mth ] ]
+    ^ self workingCopy packageExtensionsFiltered:
+	    [:mth |
+	    extensionMethods isNil or: [ extensionMethods includes: mth ] ]
 
     "Created: / 14-05-2009 / 11:32:01 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
 shouldFileOutClass: class
 
-    "Do not fileout autoloaded classes, 
+    "Do not fileout autoloaded classes,
     they are untouched"
     class isLoaded ifFalse:[^false].
 
-    class theNonMetaclass 
-        methodsDo:[:mth|(self shouldFileOutMethod: mth) ifTrue:[^true]].
-    class theMetaclass 
-        methodsDo:[:mth|(self shouldFileOutMethod: mth) ifTrue:[^true]].
+    class theNonMetaclass
+	methodsDo:[:mth|(self shouldFileOutMethod: mth) ifTrue:[^true]].
+    class theMetaclass
+	methodsDo:[:mth|(self shouldFileOutMethod: mth) ifTrue:[^true]].
     ^false
 
     "
-        CommitTask basicNew 
-            package: #'stx:goodies/libsvn';
-            shouldFileOutClass: CommitTask
+	CommitTask basicNew
+	    package: #'stx:goodies/libsvn';
+	    shouldFileOutClass: CommitTask
 
-        CommitTask basicNew 
-            package: #'stx:libbasic';
-            shouldFileOutClass: Object      
+	CommitTask basicNew
+	    package: #'stx:libbasic';
+	    shouldFileOutClass: Object
     "
 
     "Created: / 24-06-2009 / 19:04:48 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -264,16 +264,16 @@
 shouldFileOutMethod: mth
 
     ^mth package = package and:
-        [mth getSourcePosition isNil]
+	[mth getSourcePosition isNil]
 
     "
-        CommitTask basicNew 
-            package: #'stx:goodies/libsvn';
-            shouldFileOutMethod: (CommitTask >> #shouldFileOutMethod:)
+	CommitTask basicNew
+	    package: #'stx:goodies/libsvn';
+	    shouldFileOutMethod: (CommitTask >> #shouldFileOutMethod:)
 
-        CommitTask basicNew 
-            package: #'stx:libbasic';
-            shouldFileOutMethod: (Object >> #yourself)
+	CommitTask basicNew
+	    package: #'stx:libbasic';
+	    shouldFileOutMethod: (Object >> #yourself)
     "
 
     "Created: / 24-06-2009 / 19:07:27 / Jan Vrany <vranyj1@fel.cvut.cz>"
--- a/SVN__InfoCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__InfoCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#InfoCommand
+WCPathCommand subclass:#InfoCommand
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -21,30 +21,30 @@
     "Modified: / 15-06-2009 / 12:06:29 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
-svnCmdArgumentsOn:arg 
+svnCmdArgumentsOn:arg
     "raise an error: must be redefined in concrete subclass(es)"
 
-    arg 
-        nextPut:'--xml'
+    arg
+	nextPut:'--xml'
 
     "Created: / 15-03-2008 / 21:56:01 / janfrog"
     "Modified: / 15-06-2009 / 12:18:12 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
-svnParseXML: doc 
-    ^ ((doc root childNodes 
-        collect: [:entryNode | WCEntryInfo readFromXml: entryNode ]) 
-            asSortedCollection: [:a :b | a path < b path ]) asOrderedCollection
+svnParseXML: doc
+    ^ ((doc root childNodes
+	collect: [:entryNode | WCEntryInfo readFromXml: entryNode ])
+	    asSortedCollection: [:a :b | a path < b path ]) asOrderedCollection
 
     "Created: / 15-03-2008 / 22:05:01 / janfrog"
     "Modified: / 16-03-2008 / 08:44:49 / janfrog"
     "Modified: / 15-06-2009 / 12:23:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
-svnProcessCommandOutput:out err:err 
+svnProcessCommandOutput:out err:err
     ^ self svnParseXML:((XML::XMLParser on:out)
-                validate:false;
-                scanDocument)
+		validate:false;
+		scanDocument)
 
     "Created: / 03-10-2008 / 16:31:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
--- a/SVN__MoveCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__MoveCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#MoveCommand
+WCCommand subclass:#MoveCommand
 	instanceVariableNames:'src dst'
 	classVariableNames:''
 	poolDictionaries:''
@@ -46,13 +46,13 @@
     "Created: / 16-03-2008 / 10:22:26 / janfrog"
 !
 
-svnCmdArgumentsOn:arg 
+svnCmdArgumentsOn:arg
     "raise an error: must be redefined in concrete subclass(es)"
 
     super svnCmdArgumentsOn:arg.
-    arg 
-        nextPut: src;
-        nextPut: dst
+    arg
+	nextPut: src;
+	nextPut: dst
 
     "Created: / 16-03-2008 / 10:22:26 / janfrog"
 ! !
--- a/SVN__PropsetCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__PropsetCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#PropsetCommand
+WCPathCommand subclass:#PropsetCommand
 	instanceVariableNames:'name value'
 	classVariableNames:''
 	poolDictionaries:''
@@ -46,13 +46,13 @@
     "Created: / 10-10-2008 / 12:43:04 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
-svnCmdArgumentsOn:arg 
+svnCmdArgumentsOn:arg
     "raise an error: must be redefined in concrete subclass(es)"
 
-    arg 
-        nextPut: name;
-        nextPut: value;
-        nextPutAll:paths asArray
+    arg
+	nextPut: name;
+	nextPut: value;
+	nextPutAll:paths asArray
 
     "Created: / 10-10-2008 / 12:44:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
--- a/SVN__RevertCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__RevertCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#RevertCommand
+WCPathCommand subclass:#RevertCommand
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -23,8 +23,8 @@
 svnCmdArgumentsOn:argStream
 
     argStream
-        nextPut:'--recursive';
-        nextPut:'.'
+	nextPut:'--recursive';
+	nextPut:'.'
 
     "Created: / 28-10-2008 / 08:50:47 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
--- a/SVN__RevisionLogEntry.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__RevisionLogEntry.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#RevisionLogEntry
+XMLObject subclass:#RevisionLogEntry
 	instanceVariableNames:'revision author date message changedPaths'
 	classVariableNames:''
 	poolDictionaries:''
@@ -68,13 +68,13 @@
 
 !RevisionLogEntry methodsFor:'instance creation'!
 
-readFromXml: xml 
+readFromXml: xml
     revision := Revision number: xml @ 'revision'.
     author := (xml / 'author') characterData.
     date := Timestamp readISO8601From: (xml / 'date') characterData.
     message := (xml / 'msg') characterData.
-    changedPaths := (xml / 'paths' / 'path') 
-                collect: [:e | WCActionNotification readFromXml: e ].
+    changedPaths := (xml / 'paths' / 'path')
+		collect: [:e | WCActionNotification readFromXml: e ].
 
     "Created: / 11-04-2008 / 13:27:47 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 18-08-2009 / 14:38:48 / Jan Vrany <vranyj1@fel.cvut.cz>"
--- a/SVN__StatusCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__StatusCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#StatusCommand
+WCPathCommand subclass:#StatusCommand
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -20,12 +20,12 @@
     "Created: / 15-03-2008 / 21:56:01 / janfrog"
 !
 
-svnCmdArgumentsOn:arg 
+svnCmdArgumentsOn:arg
     "raise an error: must be redefined in concrete subclass(es)"
 
-    arg 
-        nextPut:'--xml';
-        nextPut:'--verbose'
+    arg
+	nextPut:'--xml';
+	nextPut:'--verbose'
 
     "Created: / 15-03-2008 / 21:56:01 / janfrog"
 !
@@ -33,10 +33,10 @@
 svnParseXML: doc
 
     ^((doc root childNodes anyOne childNodes
-        collect:
-            [:entryNode|
-            (WCEntry readFromXml: entryNode) wc: workingCopy; yourself]) asSortedCollection:[:a :b|a path < b path])
-            asOrderedCollection
+	collect:
+	    [:entryNode|
+	    (WCEntry readFromXml: entryNode) wc: workingCopy; yourself]) asSortedCollection:[:a :b|a path < b path])
+	    asOrderedCollection
 
     "Created: / 15-03-2008 / 22:05:01 / janfrog"
     "Modified: / 16-03-2008 / 08:44:49 / janfrog"
@@ -44,10 +44,10 @@
     "Modified: / 27-08-2009 / 09:51:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-svnProcessCommandOutput:out err:err 
+svnProcessCommandOutput:out err:err
     ^ self svnParseXML:((XML::XMLParser on:out)
-                validate:false;
-                scanDocument)
+		validate:false;
+		scanDocument)
 
     "Created: / 03-10-2008 / 16:31:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
--- a/SVN__TestCase.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__TestCase.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#TestCase
+Smalltalk::TestCase subclass:#TestCase
 	instanceVariableNames:'workdir package manager repo wc branch'
 	classVariableNames:''
 	poolDictionaries:''
--- a/SVN__UpdateCommand.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__UpdateCommand.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#UpdateCommand
+UpdateLikeCommand subclass:#UpdateCommand
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
--- a/SVN__WCEntryInfo.st	Mon Oct 19 14:25:27 2009 +0200
+++ b/SVN__WCEntryInfo.st	Mon Oct 19 14:52:48 2009 +0200
@@ -2,7 +2,7 @@
 
 "{ NameSpace: SVN }"
 
-nil subclass:#WCEntryInfo
+XMLObject subclass:#WCEntryInfo
 	instanceVariableNames:'path kind revision author date'
 	classVariableNames:''
 	poolDictionaries:''
@@ -54,13 +54,13 @@
 
 !WCEntryInfo methodsFor:'initialization'!
 
-readFromXml: xmlNode 
+readFromXml: xmlNode
     path := xmlNode @ 'path'.
     kind := xmlNode @ 'kind'.
     revision := ((xmlNode / 'commit') @ 'revision') asNumber.
     author := (xmlNode / 'commit' / 'author') characterData.
-    date := Timestamp 
-                readISO8601From: (xmlNode / 'commit' / 'date') characterData.
+    date := Timestamp
+		readISO8601From: (xmlNode / 'commit' / 'date') characterData.
 
     "Modified: / 06-04-2008 / 21:36:51 / janfrog"
     "Created: / 15-06-2009 / 12:23:09 / Jan Vrany <vranyj1@fel.cvut.cz>"