SourceCodeManagerUtilities.st
branchjv
changeset 3838 474d8ec95b33
parent 3434 a140fb9f5970
parent 3818 25607a4f1e98
child 3849 3c85146be3fa
--- a/SourceCodeManagerUtilities.st	Tue Feb 04 21:01:56 2014 +0100
+++ b/SourceCodeManagerUtilities.st	Wed Apr 01 10:37:40 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2000 eXept Software AG
               All Rights Reserved
@@ -11,10 +13,12 @@
 "
 "{ Package: 'stx:libbasic3' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#SourceCodeManagerUtilities
 	instanceVariableNames:'manager resources confirmNewFiles'
 	classVariableNames:'LastSourceLogMessage LastModule LastPackage YesToAllQuery
-		YesToAllNotification LastSourceLogMessages'
+		YesToAllNotification LastSourceLogMessages DefaultUtilities'
 	poolDictionaries:''
 	category:'System-SourceCodeManagement'
 !
@@ -92,8 +96,8 @@
 
 default
 
-    Default isNil ifTrue:[Default := SourceCodeManagerUtilitiesForContainerBasedManagers new].
-    ^Default
+    DefaultUtilities isNil ifTrue:[DefaultUtilities := SourceCodeManagerUtilitiesForContainerBasedManagers new].
+    ^ DefaultUtilities
 
     "Created: / 10-10-2011 / 11:28:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 26-07-2012 / 20:31:52 / cg"
@@ -674,13 +678,6 @@
 
 !SourceCodeManagerUtilities methodsFor:'accessing'!
 
-classResources
-
-    ^self class classResources
-
-    "Created: / 10-10-2011 / 11:42:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
 confirmNewFiles:aBoolean
     "if true, ask if new files are about to be added to the repo"
 
@@ -736,7 +733,7 @@
 
 initialize
     confirmNewFiles := true.
-    resources := self classResources.
+    resources := self class classResources.
 
     "Modified: / 13-10-2011 / 11:03:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 24-07-2012 / 18:17:57 / cg"
@@ -895,7 +892,7 @@
 !
 
 validateConsistencyOfPackage:aPackage doClasses:doClasses doExtensions:doExtensions
-    |checker report msg answer dialog|
+    |checker report msg answer dialog problems numProblems|
 
     "/ also done by ProjectChecker...
     "/ defClass := aPackage asPackageId projectDefinitionClass.
@@ -904,14 +901,15 @@
     checker := ProjectChecker new.
     checker checkExtensionsOnly:(doClasses not and:[ doExtensions ]).
     report := checker check: aPackage.
-    (report notNil and:[report problems notEmptyOrNil]) ifTrue:[
-        report problems size == 1 ifTrue:[
+    (report notNil and:[(problems := report problems) notEmptyOrNil]) ifTrue:[
+        numProblems := problems size.
+        numProblems == 1 ifTrue:[
             msg := 'The ProblemChecker found the following error/inconsistency:\\    %2\\Need more detail or help for repair?'
         ] ifFalse:[
             msg := 'The ProblemChecker found %1 errors/inconsistencies.\\Browse them for detail or repair?'
         ].
-        answer := Dialog confirmWithCancel:(msg bindWith:report problems size 
-                                                with:report problems first label) withCRs.
+        answer := Dialog confirmWithCancel:(msg bindWith:numProblems 
+                                                with:problems first label) withCRs.
         answer isNil ifTrue:[
             "/ cancel
             AbortOperationRequest raiseRequest
@@ -920,7 +918,7 @@
             dialog := Tools::ProjectCheckerBrowser new.
             dialog
                 projectChecker: (ProjectChecker forPackage: aPackage);
-                problemList:report problems;
+                problemList:problems;
                 showCancel:true;
                 openModal.
 
@@ -1166,6 +1164,303 @@
     "Created: / 29-12-2011 / 14:35:06 / cg"
 !
 
+checkOutPackages: packages askForRevision: askForRevision
+    "Updates code of given packages (loaded in the image) to a specific revision.
+     If `askForRevision` is true, then user is asked to specify to which revision to
+     update. If `askForRevision` is false, then packages are updated to a 'newest'
+     revision. 
+
+     NOTE: Definition of `newest` revision may vary. For SCMs which allows for multiple
+     heads, it is not clear which one it is. In that case, even if `askForRevision` is
+     false, this method may result in user interation, asking user to select which of the
+     newest she wants.
+
+     NOTE: Naming is bit confusing, it should be something like #updatePackages:ask...
+     but to keep this in line with other methods, we use #checkOutPackages"
+
+    ^ self subclassResponsibility.
+
+    "Created: / 01-04-2014 / 21:50:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+checkinClass:aClass
+    "check a class into the source repository.
+     Asks interactively for a log-message."
+
+    ^ self checkinClass:aClass withInfo:nil
+!
+
+checkinClass:aClass withInfo:aLogInfoOrNil
+    "check a class into the source repository.
+     If the argument, aLogInfoOrNil isNil, ask interactively for a log-message."
+
+    ^ self checkinClass:aClass withInfo:aLogInfoOrNil withCheck:true
+!
+
+checkinClass:aClass withInfo:aLogInfoOrNil withCheck:doCheckClass
+    "check a class into the source repository.
+     If the argument, aLogInfoOrNil isNil, ask interactively for log-message.
+     If doCheckClass is true, the class is checked for send of halts etc."
+
+    ^ self 
+        checkinClass:aClass 
+        withInfo:aLogInfoOrNil 
+        withCheck:doCheckClass 
+        usingManager:(self sourceCodeManagerFor:aClass)
+
+    "Modified: / 21-12-2011 / 18:19:55 / cg"
+!
+
+checkinClass:aClass withInfo:aLogInfoOrNil withCheck:doCheckClassHolder usingManager:managerOrNil
+    "check a class into the source repository.
+     If the argument, aLogInfoOrNil isNil, ask interactively for log-message.
+     If doCheckClass is true, the class is checked for send of halts etc."
+
+    |logMessage checkinInfo mgr pri|
+
+    aClass isLoaded ifFalse:[
+        self information:(resources string:'Cannot checkin unloaded classes (%1)' with:aClass name).
+        ^ false.
+    ].
+
+    mgr := managerOrNil.
+    mgr isNil ifTrue:[
+        mgr := self sourceCodeManagerFor:aClass.
+        mgr isNil ifTrue:[
+            ^ false
+        ]
+    ].
+
+    self ensureCorrectVersionMethodsInClass:aClass usingManager:mgr.
+    mgr supportsCheckinLogMessages ifTrue:[
+        (self 
+            getLogMessageForClassCheckinTakingDefaultsFromPreviousLogInfo:aLogInfoOrNil 
+            forClass:aClass
+            valuesInto:[:logMessageRet :checkinInfoRet |
+                logMessage := logMessageRet.
+                checkinInfo := checkinInfoRet.
+            ]
+        ) ifFalse:[^ false].
+    ].
+
+    (self classIsNotYetInRepository:aClass withManager:mgr) ifTrue:[
+        (self createSourceContainerForClass:aClass usingManager:mgr) ifFalse:[
+"/            self warn:'did not create a container for ''' , aClass name , ''''.
+            ^ false
+        ].
+        ^ true.
+    ].
+
+    self activityNotification:(resources string:'checking in %1' with:aClass name).
+    pri := Processor activePriority.
+    Processor activeProcess withPriority:pri-1 to:pri
+    do:[
+        |revision aborted freshCreated|
+
+        freshCreated := false.
+        revision := aClass revision.
+        revision isNil ifTrue:[ 
+            mgr isContainerBased ifTrue:[
+                "/ mhmh - check if it has a container.
+                (mgr checkForExistingContainerForClass:aClass) ifFalse:[
+                    (self createSourceContainerForClass:aClass usingManager:mgr) ifFalse:[
+                        self warn:'Did not create/change repository container for ''' , aClass name allBold , ''''.
+                        ^ false.
+                    ].
+                    freshCreated := true.
+                ]
+            ]
+        ].
+
+        doCheckClassHolder value ifTrue:[
+            "/ check if the class contains halts, error-sends etc.
+            (self checkAndWarnAboutBadMessagesInClass:aClass checkAgainHolder:doCheckClassHolder) ifFalse:[
+                ^ false
+            ].
+        ].
+
+        freshCreated ifFalse:[
+            aborted := false.
+            AbortOperationRequest handle:[:ex |
+                aborted := true.
+                ex return.
+            ] do:[
+                |checkinState cause|
+                checkinState := false.
+                cause := ''.
+                [
+                    checkinState := mgr checkinClass:aClass logMessage:logMessage
+                ] on:SourceCodeManagerError do:[:ex| 
+                    cause := ex description.
+                    "/ ex proceed.
+                ].
+
+                checkinState ifFalse:[
+                    Transcript showCR:'checkin of ''' , aClass name , ''' failed - ', cause.
+                    self warn:(resources stringWithCRs:'Checkin of "%1" failed\\' with:aClass name allBold),cause.
+                    AbortOperationRequest raise.
+                    "/ ^ false.
+                ].
+                checkinInfo notNil ifTrue:[
+                    checkinInfo isStable ifTrue:[
+                        "set stable tag for class that has been checked in"
+                        self tagClass:aClass as:#stable.
+                    ].
+                    checkinInfo tagIt ifTrue:[
+                        "set any additional tags for the class that has been checked in"
+                        (checkinInfo tag asCollectionOfSubstringsSeparatedByAny:',;') do:[:eachTag |
+                            self tagClass:aClass as:eachTag withoutSeparators.
+                        ].
+                    ].
+                    CVSSourceCodeManager recentTag:checkinInfo tag.
+                ].
+            ].
+            aborted ifTrue:[
+                Transcript showCR:'Checkin of ''' , aClass name , ''' aborted'.
+
+                AbortAllOperationWantedQuery query ifTrue:[
+                    (Dialog 
+                        confirm:(resources stringWithCRs:'Checkin of "%1" aborted.\\Cancel all ?' with:aClass name)
+                        default:false)
+                    ifTrue:[
+                        AbortAllOperationRequest raise.
+                    ]
+                ].
+                ^ false.
+            ].
+        ].
+    ].
+    ^ true
+
+    "Created: / 21-12-2011 / 18:19:14 / cg"
+!
+
+checkinClasses:aCollectionOfClass
+    "check a collection of classes into the source repository.
+     Asks interactively for log-message."
+
+    ^ self checkinClasses:aCollectionOfClass withInfo:nil
+!
+
+checkinClasses:aCollectionOfClasses withInfo:aLogInfoOrNil
+    "check a bunch of classes into the source repository.
+     If the argument, aLogInfoOrNil isNil, ask interactively for log-message."
+
+    |checkClassWhenCheckingInHolder|
+
+    checkClassWhenCheckingInHolder := ValueHolder with:(UserPreferences current at:#checkClassesWhenCheckingIn ifAbsent:true).
+    checkClassWhenCheckingInHolder 
+        onChangeEvaluate:[ UserPreferences current at:#checkClassesWhenCheckingIn put:checkClassWhenCheckingInHolder value ].
+
+    ^ self
+        checkinClasses:aCollectionOfClasses 
+        withInfo:aLogInfoOrNil 
+        withCheck:checkClassWhenCheckingInHolder
+!
+
+checkinClasses:aCollectionOfClasses withInfo:aLogInfoOrStringNil withCheck:doCheckClassesHolder
+    "check a bunch of classes into the source repository.
+     If the argument, aLogInfoOrStringNil isNil, ask interactively for log-message."
+
+    self checkinClasses:aCollectionOfClasses withInfo:aLogInfoOrStringNil withCheck:doCheckClassesHolder usingManager:nil
+
+    "Modified: / 21-12-2011 / 18:24:47 / cg"
+!
+
+checkinClasses:aCollectionOfClasses withInfo:aLogInfoOrStringOrNil withCheck:doCheckClassesHolder usingManager:aManagerOrNil
+    "check a bunch of classes into the source repository.
+     If the argument, aLogInfoOrStringOrNil isNil, ask interactively for log-message."
+
+    |classes allClasses checkinInfoOrString yesOrNoToAll unchangedClasses|
+
+    "/ ignore private classes
+    classes := aCollectionOfClasses select:[:aClass | aClass owningClass isNil].
+    classes isEmpty ifTrue:[
+        self information:'Only private classes given - nothing checked in.'.
+        ^ self
+    ].
+    classes := classes select:[:aClass | aClass isLoaded].
+    classes isEmpty ifTrue:[
+        self information:'Only unloaded classes given - nothing checked in.'.
+        ^ self
+    ].
+
+    classes size == 1 ifTrue:[
+        ^ self checkinClass:classes first withInfo:aLogInfoOrStringOrNil withCheck:doCheckClassesHolder usingManager:aManagerOrNil.
+    ].
+
+    "ask once, for all classes"
+    aLogInfoOrStringOrNil isNil ifTrue:[
+        checkinInfoOrString := self 
+                        getCheckinInfoFor:(resources string:'%1 classes to checkin' with:aCollectionOfClasses size)
+                        initialAnswer:nil
+                        withQuickOption:true.
+        checkinInfoOrString isNil ifTrue:[^ self].
+    ] ifFalse:[
+        checkinInfoOrString := aLogInfoOrStringOrNil.
+    ].
+
+    allClasses := classes.    
+    (checkinInfoOrString isString not and:[checkinInfoOrString quickCheckIn]) ifTrue:[
+        "/ not only the one's in the changeSet;
+        "/ also those which have not been checked in before.
+        classes := classes select:[:each | each hasUnsavedChanges or:[ (each revisionOfManager:aManagerOrNil) isNil ]].
+        classes isEmpty ifTrue:[ Dialog information:'no changes to checkin (quickCheckIn)' ]
+    ].
+
+    "abortAll is handled, and also asked for here!!"
+    AbortAllOperationRequest handleAndAnswerQueryIn:[
+        classes notEmpty ifTrue:[
+            self yesToAllNotification handle:[:ex |
+                yesOrNoToAll := ex parameter.
+                ex proceed
+            ] do:[
+                self yesToAllQuery handle:[:ex |
+                    ex proceedWith:yesOrNoToAll
+                ] do:[
+                    classes do:[:aClass |
+                        self activityNotification:(resources string:'checking in %1' with:aClass name).
+                        "/ ca does not want boxes to pop up all over ...
+                        UserInformation handle:[:ex |
+                            Transcript showCR:ex description.
+                            ex proceed.
+                        ] do:[
+                            AbortOperationRequest catch:[
+                                self 
+                                    checkinClass:aClass 
+                                    withInfo:checkinInfoOrString 
+                                    withCheck:doCheckClassesHolder
+                                    usingManager:aManagerOrNil
+                            ]
+                        ].
+                    ].
+                ]
+            ].
+        ].
+
+        (checkinInfoOrString isString not and:[ (checkinInfoOrString isStable or:[checkinInfoOrString tagIt]) ])
+        ifTrue:[
+            "/mhmh - but tag should be set on all (even unchanged ones)
+            "/ the other onces have already been tagged
+            unchangedClasses := allClasses reject:[:eachClass | (classes includes:eachClass)].
+
+            "mhmh - could still have to tag them"
+            checkinInfoOrString isStable ifTrue:[
+                unchangedClasses do:[:eachClass |
+                    self tagClass:eachClass as:#stable.
+                ].
+            ].
+            checkinInfoOrString tagIt ifTrue:[
+                unchangedClasses do:[:eachClass |
+                    self tagClass:eachClass as:(checkinInfoOrString tag).
+                ].
+            ].
+        ].
+    ].
+
+    "Created: / 21-12-2011 / 18:24:25 / cg"
+!
+
 checkoutClass:aClass askForMerge:askForMerge
     "check-out a class from the source repository."
 
@@ -1879,12 +2174,12 @@
 
     rev := classToCompare revisionInfoOfManager:mgr.
 "/    rev := classToCompare binaryRevision.
-    revisionInClass := classToCompare revision.
+    revisionInClass := classToCompare revisionOfManager:mgr.
     rev isNil ifTrue:[
         rev := revisionInClass
     ].
     rev isNil ifTrue:[
-        (Dialog confirm:'Class seems to be not yet in the repository (or classes revision info is corrupted)\\Proceed ?' withCRs)
+        (Dialog confirm:'Class seems to be not yet in the repository (or classes revision info is missing or corrupted)\\Proceed ?' withCRs)
         ifFalse:[
             ^ self
         ]
@@ -1895,12 +2190,11 @@
     "/
     SourceCodeManagerError handle:[:ex |
         Dialog warn:(resources 
-                                stringWithCRs:'Could not fetch source of "%1".\\Please check your sourcecode manager settings of %2 for package: "%3".\(and possibly the network for reachability of the repository)'
+                                stringWithCRs:'Could not fetch revision info of "%1".\\Please check your sourcecode manager settings of %2 for package: "%3".\(and possibly the network for reachability of the repository)'
                                 with:classToCompare name
                                 with:classToCompare sourceCodeManager managerTypeName
                                 with:classToCompare package).
         ^ self.
-
     ] do:[
         newestRev := mgr newestRevisionOf:classToCompare.
     ].
@@ -1927,7 +2221,21 @@
         rev := newestRev.
     ].
 
-    rev notNil ifTrue:[
+    rev isNil ifTrue:[
+        mgr = classToCompare sourceCodeManager ifTrue:[
+            msg := 'Could not figure out the newest revision of "%1".\\Please check if this class is really contained in that repository,\and also your sourcecode manager settings of %2 for package: "%3".\(and possibly the network for reachability of the repository)'
+        ] ifFalse:[
+            msg := 'Could not figure out the newest revision of "%1".\\Notice that the class is actually maintained by %4, not %2.\Please check if this class is really in the %2 repository,\and also your sourcecode manager settings of %2 for package: "%3".\(and possibly the network for reachability of the repository)'
+        ].
+        Dialog warn:(resources 
+                                stringWithCRs:msg
+                                with:classToCompare name
+                                with:mgr managerTypeName
+                                with:classToCompare package
+                                with:(classToCompare sourceCodeManager managerTypeName)).
+        ^ self.
+        
+    ] ifFalse:[
         rev withoutSpaces isEmpty ifTrue:[
             msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
             "/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
@@ -1972,15 +2280,28 @@
 
             self activityNotification:'comparing...'.
 
-            brwsr := (UserPreferences versionDiffViewerClass)
-                  openOnClass:classToCompare
-                  labelA:('Repository: ' , revString)
-                  sourceA:comparedSource
-                  labelB:('Current: (based on: ' , thisRevString , ')')
-                  sourceB:currentSource
-                  title:('Comparing ' , classToCompare name)
-                  ifSame:[versionsAreTheSame := true].
-
+            ChangeSet invalidChangeChunkError handle:[:ex |
+                |answer|
+
+                answer := Dialog 
+                            confirm:(resources 
+                                stringWithCRs:'An invalid change chunk was encountered when reading the source of %1.\This may be due to a currupted source file (or source file was modified/updated in the meantime, without recompilation).\\Proceed in debugger?'
+                                with:aClass)
+                            yesLabel:(resources string:'Debug')
+                            noLabel:(resources string:'Cancel')
+                            initialAnswer:false.
+                answer ifTrue:[ex reject].
+                AbortOperationRequest raise.
+            ] do:[
+                brwsr := (UserPreferences versionDiffViewerClass)
+                      openOnClass:classToCompare
+                      labelA:('Repository: ' , revString)
+                      sourceA:comparedSource
+                      labelB:('Current: (based on: ' , thisRevString , ')')
+                      sourceB:currentSource
+                      title:('Comparing ' , classToCompare name)
+                      ifSame:[versionsAreTheSame := true].
+            ].
             versionsAreTheSame ifFalse:[
                 brwsr classChangeSet 
                     classBeingCompared:classToCompare;
@@ -2029,6 +2350,24 @@
     "Modified: / 24-07-2012 / 18:11:27 / cg"
 !
 
+comparePackages:packages askForRevision:askForRevision 
+    "Compares code of given packages (loaded in the image) against a specific revision
+     and opens a diff browser on differences.
+
+     If `askForRevision` is true, then user is asked to specify to which revision to
+     update. If `askForRevision` is false, then packages are updated to a 'newest'
+     revision. 
+
+     NOTE: Definition of `newest` revision may vary. For SCMs which allows for multiple
+     heads, it is not clear which one it is. In that case, even if `askForRevision` is
+     false, this method may result in user interation, asking user to select which of the
+     newest she wants."
+
+    ^ self subclassResponsibility.
+
+    "Created: / 04-04-2014 / 15:23:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 compareProject:aProject withRepositoryVersionFrom:aDateOrNilForNewest
     |diffSet|
 
@@ -2192,6 +2531,9 @@
 "/            ]
 "/        ]
     ].
+    directory isEmptyOrNil ifTrue:[
+        directory := LastPackage.
+    ].
 
     fileName isNil ifTrue:[
         fileName := (Smalltalk fileNameForClass:aClass) , '.st'.
@@ -2257,6 +2599,9 @@
                 module := rslt at:#module.
                 directory := rslt at:#package.
                 fileName := rslt at:#fileName.
+                (module isEmptyOrNil or:[directory isEmptyOrNil or:[fileName isEmptyOrNil]]) ifTrue:[
+                    ^ false
+                ].
             ]
         ].
         (fileName endsWith:',v') ifTrue:[
@@ -2614,7 +2959,11 @@
             [
                 s := SourceCodeManager
                         streamForClass:nil fileName:eachSTFile revision:#newest directory:directory module:module cache:true.
-                chgSet := ChangeSet fromStream:s.
+                s isNil ifTrue:[
+                    chgSet := ChangeSet new
+                ] ifFalse:[
+                    chgSet := ChangeSet fromStream:s.
+                ]
             ] ensure:[
                 s notNil ifTrue:[s close].
             ].
@@ -2718,7 +3067,7 @@
 !
 
 ensureCorrectVersionMethodsInClass:aClass usingManager:aManager
-    |theMetaclass src newSrc versionMethodName oldVersionMethodName|
+    |theMetaclass versionMthd src newSrc versionMethodName oldVersionMethodName|
 
     theMetaclass := aClass theMetaclass.
     versionMethodName := aManager nameOfVersionMethodInClasses.
@@ -2729,23 +3078,28 @@
 "/            theMetaclass removeSelector:oldVersionMethodName.   
 "/        ].
         "/ ensure that my version method is parsable (contains $'s)
-        src := (theMetaclass compiledMethodAt:versionMethodName) source.
-        src notNil ifTrue:[
-            newSrc := aManager ensureDollarsInVersionMethod:src.
-            newSrc ~= src ifTrue:[
-                theMetaclass compile:newSrc.
-            ]
+        versionMthd := theMetaclass compiledMethodAt:versionMethodName.
+        versionMthd notNil ifTrue:[
+            src := versionMthd source.
+            src notNil ifTrue:[
+                newSrc := aManager ensureDollarsInVersionMethod:src.
+                newSrc ~= src ifTrue:[
+                    theMetaclass compile:newSrc categorized:#documentation.
+                ]
+            ].
         ].
     ] ifFalse:[
         (theMetaclass includesSelector:oldVersionMethodName) ifTrue:[
             "/ but make sure, it is a version method for this sourcecodemanager...
             (theMetaclass methodDictionary keys count:[:sel | sel startsWith:'version']) size == 1 ifTrue:[
-                src := (theMetaclass compiledMethodAt:oldVersionMethodName) source.
-                (src startsWith:oldVersionMethodName) ifTrue:[
-                    newSrc := versionMethodName 
-                              , (src copyFrom:(oldVersionMethodName size + 1))
-                ].
-                theMetaclass compile:newSrc.
+                versionMthd := theMetaclass compiledMethodAt:oldVersionMethodName.
+                versionMthd notNil ifTrue:[
+                    src := versionMthd source.
+                    (src startsWith:oldVersionMethodName) ifTrue:[
+                        newSrc := versionMethodName , (src copyFrom:(oldVersionMethodName size + 1))
+                    ].
+                    theMetaclass compile:newSrc categorized:#documentation.
+                ]
             ]
         ].
     ].
@@ -2765,7 +3119,7 @@
     aLogInfoOrNil isNil ifTrue:[
         initialLogMessage := (self goodInitialLogMessageForCheckinClassOfClass:aClass) ? ''.
         "/ initial checkin ?
-        (aClass package isNil or:[aClass revision isNil]) ifTrue:[ 
+        (aClass package isNil or:[(aClass revisionOfManager:manager) "revision" isNil]) ifTrue:[ 
             initialLogMessage := 'initial checkin\\' withCRs , initialLogMessage
         ].
         checkinInfo := self 
@@ -2798,7 +3152,7 @@
 removeSourceContainerForClass:aClass confirm:doConfirm warn:doWarn
     "show container & optionally let user confirm twice."
 
-    |module directory fileName info mgr|
+    |info mgr|
 
     aClass isLoaded ifFalse:[
         doWarn ifTrue:[
@@ -2817,6 +3171,32 @@
     ].
 
     info := mgr sourceInfoOfClass:aClass.
+    ^ self removeSourceContainerForClass:aClass usingSourceInfo:info confirm:doConfirm warn:doWarn
+
+    "Modified: / 16-07-2013 / 19:46:50 / cg"
+!
+
+removeSourceContainerForClass:aClass usingSourceInfo:info confirm:doConfirm warn:doWarn
+    "show container & optionally let user confirm twice."
+
+    |module directory fileName mgr|
+
+    aClass isLoaded ifFalse:[
+        doWarn ifTrue:[
+            self warn:(resources string:'Please load the class first.').
+        ].
+        ^ false.
+    ].
+
+    "/
+    "/ ask the sourceCodeManager if it knows anything about that class
+    "/ if so, take that as a default.
+    "/
+    mgr := self sourceCodeManagerFor:aClass.
+    mgr isNil ifTrue:[
+        ^ false
+    ].
+
     info notNil ifTrue:[
         (info includesKey:#module) ifTrue:[
             module := (info at:#module).
@@ -2848,8 +3228,8 @@
 
     OperatingSystem isMSDOSlike ifTrue:[
         "cvs expects unix-filenames"
-        module := module copyReplaceAll:$\ with:$/.
-        directory := directory copyReplaceAll:$\ with:$/.
+        module := module asUnixFilenameString.
+        directory := directory asUnixFilenameString.
     ].
     (mgr checkForExistingContainer:fileName inModule:module directory:directory) ifFalse:[
         doWarn ifTrue:[
@@ -2879,9 +3259,8 @@
         ].
     ].
 
-    (mgr removeContainer:fileName
-                inModule:module
-               directory:directory) ifFalse:[
+    (mgr removeContainer:fileName inModule:module directory:directory) 
+    ifFalse:[
         doWarn ifTrue:[
             self warn:(resources string:'failed to remove container.').
         ].
@@ -2958,12 +3337,15 @@
         s notNil ifTrue:[
             aStream nextPutLine:'  Source repository : ' , s
         ].
-        aStream nextPutLine:'  Filename ........ : ' , (info fileName ? '?').
-        aStream nextPutLine:'  Revision ........ : ' , (info revision ? '?').
-        aStream nextPutLine:'  Checkin date .... : ' , (info date  ? '?') , ' ' , 
-                                                       (info time ? '?'), ' ', 
-                                                       (info timezone ? '').
-        aStream nextPutLine:'  Checkin user .... : ' , (info user ? '?').
+        aStream nextPutLine:('  Filename ........ : %1' bindWith: (info fileName ? '?')).
+        info symbolicVersionName ~= info revision ifTrue:[
+            aStream nextPutLine:('  Symbolic Version  : %1' bindWith: (info symbolicVersionName ? '?')).
+        ].
+        aStream nextPutLine:('  Revision ........ : %1' bindWith: (info revision ? '?')).
+        aStream nextPutLine:('  Checkin date .... : %1 %2 %3' bindWith: (info date  ? '?') 
+                                                              with:(info time ? '?') 
+                                                              with:(info timezone ? '')).
+        aStream nextPutLine:('  Checkin user .... : %1' bindWith: (info user ? '?')).
     ].
 
     (info2 := aClass packageSourceCodeInfo) notNil ifTrue:[
@@ -2983,8 +3365,8 @@
             module := info2 at:#module ifAbsent:nil.
         ].
         module notNil ifTrue:[
-            aStream nextPutLine:('  Repository URL ......: ' , 
-                                ((mgr repositoryNameForPackage:aClass package) ifNil:[mgr repositoryName , ' (default)'])).
+            aStream nextPutLine:('  Repository URL ......: %1' bindWith: 
+                                ((mgr repositoryNameForPackage:aClass package) ifNil:[mgr repositoryName , ' (default)']) asString).
         ].
         mgr writeRevisionLogOf:aClass short:shortOrNot to:aStream.
     ]
@@ -3143,7 +3525,7 @@
      return a dictionary containing module, package and filename,
      or nil if canceled."
 
-    |box y component resources answer
+    |box y component answer
      moduleHolder packageHolder fileNameHolder
      module package fileName 
      allPackageIDs knownContainers knownPackages packageUpdater
@@ -3195,8 +3577,6 @@
     packageHolder := initialPackage asValue.
     fileNameHolder := initialFileName asValue.
 
-    resources := self classResources.
-
     "/
     "/ open a dialog for this
     "/
@@ -3256,7 +3636,7 @@
     box addAbortAndOkButtons.
 
     (YesToAllNotification notNil and:[YesToAllNotification isHandled]) ifTrue:[
-        component := Button label:'Yes to all'.
+        component := Button label:(resources string:'Yes to All').
         component action:[
                             YesToAllNotification queryWith:true.
                             box doAccept.
@@ -3265,7 +3645,7 @@
         box addButton:component.
     ].
     (AbortAllSignal isHandled) ifTrue:[
-        component := Button label:'Cancel all'.
+        component := Button label:(resources string:'Cancel All').
         component action:[
                             box hide.
                             AbortAllSignal raiseSignal.
@@ -3341,12 +3721,9 @@
      return a revision number, or nil if canceled."
 
     |partialLog revisions items newestRev
-     box y component resources 
-     revisionHolder symbolicNames stableRevision releasedRevision
+     box y component revisionHolder symbolicNames stableRevision releasedRevision
      tagHolder tagList lockChange|
 
-    resources := self classResources.
-
     partialLog := aSourceCodeManager
         revisionLogOf:clsOrNil
         numberOfRevisions:20
@@ -3482,7 +3859,7 @@
     ].
     box destroy.
 
-    ^ revisionHolder value withoutSpaces.
+    ^ (tagHolder value notEmptyOrNil ifTrue:[tagHolder] ifFalse:[revisionHolder]) value withoutSpaces.
 
     "
      SourceCodeManagerUtilities
@@ -3508,9 +3885,7 @@
      Only checks in non-extension methods - as this is only called when checking "
 
     |badStuff whatIsBad msg answer labels values defaultAnswer dontShowAgain
-     methodsWithBadStuff resources|
-
-    resources := Dialog classResources.
+     methodsWithBadStuff|
 
     badStuff := #(
         ( halt         'send of #halt (use for debugging only) - better use #error:''some message'' or #breakPoint:')
@@ -3576,10 +3951,10 @@
 "/            values := #(#cancelAll) , values.
 "/        ].
 
-    DialogBox aboutToOpenBoxNotificationSignal handle:[:ex |
+    Dialog modifyingBoxWith:[:box |
         checkAgainHolder isValueModel ifTrue:[
             dontShowAgain := checkAgainHolder value not asValue.
-            ex box addCheckBoxAtBottom:(resources string:'Do not show this Dialog again (reenable in Launcher).')
+            box addCheckBoxAtBottom:(resources string:'Do not show this Dialog again (reenable in Launcher).')
                 on:dontShowAgain.
         ].
     ] do:[
@@ -3587,7 +3962,7 @@
                       request:msg withCRs
                       label:(resources string:'Really CheckIn ?')
                       image:(InfoBox iconBitmap)
-                      buttonLabels:(resources array:labels)
+                      buttonLabels:(Dialog classResources array:labels)
                       values:values
                       default:defaultAnswer
                       onCancel:nil.
@@ -3703,7 +4078,7 @@
      So check the outcome."
 
     |selectorsInChangeSet newSelectors modifiedSelectors
-     classChanges changesForThisClass definitionChangesForThisClass methodChangesForThisClass 
+     className metaClassName classChanges changesForThisClass definitionChangesForThisClass methodChangesForThisClass 
      allMethodChangesForThisClass modifiedMethodsForThisClass newMethodsForThisClass removedMethodsForThisClass
      initialLogStream printSelectors selectorsWithCommentOrFormattingChangeOnly
      selectorsWithVariableChangeOnly newSelectorsRemoved
@@ -3745,10 +4120,12 @@
         ].
 
     classChanges := ChangeSet current select:[:aChange | aChange isClassChange].
+    className := aClass theNonMetaclass name.
+    metaClassName := aClass theMetaclass name.
 
     changesForThisClass := classChanges 
-                                select:[:aChange | aChange className = aClass theNonMetaclass name
-                                                   or:[aChange className = aClass theMetaclass name] ].
+                                select:[:aChange | aChange className = className
+                                                   or:[aChange className = metaClassName ]].
 
     additionalInfoPerChangedSelector := Dictionary new.
     definitionChangesForThisClass := changesForThisClass reject:[:aChange | aChange isMethodChange].
@@ -3948,19 +4325,10 @@
 !SourceCodeManagerUtilities class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/SourceCodeManagerUtilities.st,v 1.296 2014-01-23 16:11:38 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/SourceCodeManagerUtilities.st,v 1.319 2015-03-01 13:18:10 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic3/SourceCodeManagerUtilities.st,v 1.296 2014-01-23 16:11:38 stefan Exp $'
-!
-
-version_HG
-
-    ^ '$Changeset: <not expanded> $'
-!
-
-version_SVN
-    ^ 'Id:: SourceCodeManagerUtilities.st 1985 2013-01-16 11:55:57Z vranyj1                                                        '
+    ^ '$Header: /cvs/stx/stx/libbasic3/SourceCodeManagerUtilities.st,v 1.319 2015-03-01 13:18:10 cg Exp $'
 ! !