SourceCodeManagerUtilities.st
author fm
Thu, 16 Nov 2006 12:12:33 +0100
changeset 1907 30ca5aea5a7a
parent 1886 434d9a185058
child 1911 d4088b5ba0ac
permissions -rw-r--r--
dialogs defaults

"
 COPYRIGHT (c) 2000 eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic3' }"

Object subclass:#SourceCodeManagerUtilities
	instanceVariableNames:''
	classVariableNames:'LastSourceLogMessage LastModule LastPackage YesToAllQuery
		YesToAllNotification'
	poolDictionaries:''
	category:'System-SourceCodeManagement'
!

!SourceCodeManagerUtilities class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2000 eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

!

documentation
"
    utility code which is useful at more than one place
    (extracted from the browser)

    [author:]
        Claus Gittinger (cg@exept)

    [see also:]

    [instance variables:]

    [class variables:]
"
! !

!SourceCodeManagerUtilities class methodsFor:'Signal constants'!

yesToAllNotification
    YesToAllNotification isNil ifTrue:[
        YesToAllNotification := QuerySignal new.
    ].
    ^ YesToAllNotification
!

yesToAllQuery
    YesToAllQuery isNil ifTrue:[
        YesToAllQuery := QuerySignal new.
    ].
    ^ YesToAllQuery
! !

!SourceCodeManagerUtilities class methodsFor:'accessing'!

lastModule
    "return the value of the static variable 'LastModule' (automatically generated)"

    ^ LastModule
!

lastModule:something
    "set the value of the static variable 'LastModule' (automatically generated)"

    LastModule := something.
!

lastPackage
    "return the value of the static variable 'LastPackage' (automatically generated)"

    ^ LastPackage
!

lastPackage:something
    "set the value of the static variable 'LastPackage' (automatically generated)"

    LastPackage := something.
! !

!SourceCodeManagerUtilities class methodsFor:'resources'!

resourcePackage
    ^ #'stx:libtool'
! !

!SourceCodeManagerUtilities class methodsFor:'utilities'!

classIsNotYetInRepository:aClass withManager:mgr
    |info|

    info := mgr sourceInfoOfClass:aClass.

    ^ (info isNil 
    or:[(info at:#fileName ifAbsent:nil) isNil
    or:[(info at:#module ifAbsent:nil) isNil
    or:[(info at:#directory ifAbsent:nil) isNil]]])

    "Created: / 25-10-2006 / 09:43:00 / cg"
!

nameOfExtensionsContainer
    ^ 'extensions.st'
!

setPackageOfAllMethodsIn:aClass to:aPackage
    "make all methods belong to the classes project"

    |anyChange anyChangeHere|

    anyChange := false.
    aClass withAllPrivateClassesDo:[:eachClass |
        anyChangeHere := false.
        eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | 
            mthd package ~= aPackage ifTrue:[
                mthd setPackage:aPackage.
                anyChangeHere := true.
            ].
        ].
        anyChangeHere ifTrue:[
            eachClass changed:#projectOrganization
        ].
        anyChangeHere ifTrue:[anyChange := true].
    ].
    anyChange ifTrue:[
       Smalltalk changed:#projectOrganization
    ].
    ^ anyChange
!

sourceCodeManagerFor:aClass
    |mgr|

    mgr := aClass theNonMetaclass sourceCodeManager.
    mgr isNil ifTrue:[
        SourceCodeManager isNil ifTrue:[
            (self warn:'SourceCodeManagement is disabled or not configured.\\Please setup in the Launcher.' withCRs) ifFalse:[
                ^ nil
            ].
        ].
        (self confirm:'Class does not seem to provide a valid sourceCodeManager.\\Assume CVS ?' withCRs) ifFalse:[
            ^ nil
        ].
        mgr := CVSSourceCodeManager.
    ].
    ^ mgr

    "Modified: / 12-09-2006 / 14:14:35 / cg"
!

sourceCodeOfClass:aClass
    |stream src|

    stream := '' writeStream.
    Method flushSourceStreamCache.
    aClass fileOutOn:stream withTimeStamp:false.
    src := stream contents asString.
    stream close.
    ^ src
! !

!SourceCodeManagerUtilities class methodsFor:'utilities-cvs'!

changeSetForExtensionMethodsForPackage:packageToCheckOut askForRevision:askForRevision using:aSourceCodeManager
    "check-out an extension container from the source repository, and return the methods there as a change set.
     If askForRevision is false, check-out the newest version.
     Return a changeSet or nil (if any error occurred)"

    |resources directory module file
     inChangeSet extensionMethods
     aStream sourceToLoad rev msg newestRev
     listHere listRep diffSet 
     changed onlyHere onlyInRep answer labels values singleChangeSelector
     changedClasses default |

    resources := self classResources.

    directory := packageToCheckOut asPackageId directory.
    module := packageToCheckOut asPackageId module.
    file := self nameOfExtensionsContainer.

    "/
    "/ ask for revision
    "/
    newestRev := aSourceCodeManager newestRevisionInFile:file directory:directory module:module.
    askForRevision ifFalse:[
        rev := newestRev ? ''
    ] ifTrue:[
        msg := resources string:'CheckOut which revision of extensions for ''%1'': (empty for newest)' with:packageToCheckOut allBold.
        newestRev notNil ifTrue:[
            msg := msg , '\' , (resources string:'Newest in reporitory is %1.' with:newestRev)
        ].

        rev := SourceCodeManagerUtilities
                askForExistingRevision:msg 
                title:'CheckOut from repository' 
                class:nil 
                manager:aSourceCodeManager 
                module:module package:directory fileName:file.

        rev isNil ifTrue:[
            ^ nil   "/ canceled
        ].
    ].

    rev withoutSpaces isEmpty ifTrue:[
        rev := #newest.
        msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
    ] ifFalse:[
        msg := 'extracting previous %1'.
    ].
    aStream := aSourceCodeManager  
        streamForClass:nil
        fileName:file 
        revision:rev 
        directory:directory 
        module:module
        cache:true.

    aStream isNil ifTrue:[
        self warn:(resources string:'Could not extract "extensions.st" for %1 from repository' with:packageToCheckOut allBold).
        ^ nil
    ].
    aStream class readErrorSignal handle:[:ex |
        self warn:('read error while reading extracted source\\' , ex description) withCRs.
        aStream close.
        ^ nil
    ] do:[
        sourceToLoad := aStream contents asString.
    ].
    aStream close.
    ^ ChangeSet fromStream:(sourceToLoad readStream).

    "Created: / 09-10-2006 / 13:04:37 / cg"
!

checkForExistingModule:module directory:directory container:containerFileName using:mgr allowCreate:allowCreate
    |resources moduleName directoryName containerName|

    resources := self classResources.
    moduleName := module allBold.
    directoryName := directory allBold.
    containerName := containerFileName allBold.

    "/
    "/ check for the container
    "/
    (mgr checkForExistingContainer:containerFileName inModule:module directory:directory) ifFalse:[
        allowCreate ifFalse:[
            self warn:(resources string:'A container for ''%1'' does not exist in ''%2:%3''' 
                                   with:containerName with:moduleName with:directoryName) withCRs.
            ^ false
        ].
        (Dialog 
            confirm:(resources string:'''%1'' is a new container (in ''%2:%3'').\\Create it ?' 
                                 with:containerName with:moduleName with:directoryName) withCRs
            noLabel:'Cancel') 
        ifFalse:[
            ^ false.
        ].
        (mgr createContainerForText:'' inModule:module package:directory container:containerFileName) ifFalse:[
            self warn:(resources string:'Cannot create new container: ''%1'' (in ''%2:%3'')' 
                                 with:containerName with:moduleName with:directoryName).
            ^ false.
        ]
    ].
    ^ true.

    "Modified: / 13-09-2006 / 18:24:57 / cg"
!

checkForExistingModule:module directory:directory using:mgr allowCreate:allowCreate
    |resources moduleNameBold directoryNameBold|

    resources := self classResources.
    moduleNameBold := module allBold.
    directoryNameBold := directory allBold.

    "/
    "/ check for the directory
    "/
    (mgr checkForExistingModule:module directory:directory) ifFalse:[
        allowCreate ifFalse:[
            self warn:(resources string:'A directory for ''%1'' does not exist in module ''%2''' 
                                   with:directoryNameBold with:moduleNameBold) withCRs.
            ^ false
        ].
        (Dialog 
            confirm:(resources string:'''%1'' is a new directory in module ''%2''.\\create it ?' 
                                 with:directoryNameBold with:moduleNameBold) withCRs
            noLabel:'Cancel') 
        ifFalse:[
            ^ false.
        ].
        (mgr createModule:module directory:directory) ifFalse:[
            self warn:(resources string:'Cannot create new directory: ''%1'' in module ''%2''' 
                                   with:directoryNameBold with:moduleNameBold) withCRs.
            ^ false.
        ]
    ].
    ^ true.

    "Modified: / 06-10-2006 / 17:08:08 / cg"
!

checkForExistingModule:module using:mgr allowCreate:allowCreate
    |resources moduleName answer|

    (mgr checkForExistingModule:module) ifFalse:[
        resources := self classResources.
        moduleName := module allBold.

        allowCreate ifFalse:[
            self warn:(resources stringWithCRs:'A module named ''%1'' does not exist in the repository' 
                                  with:moduleName) .
            ^ false
        ].
        AbortAllOperationRequest isHandled ifTrue:[
            answer := Dialog 
                confirmWithCancel:(resources stringWithCRs:'''%1'' is a new module.\\create it ?' with:moduleName)
                labels:(resources array:#('Cancel All' 'Cancel' 'Yes' )).
            answer isNil ifTrue:[ AbortAllOperationRequest raise ].
        ] ifFalse:[
            answer := Dialog 
                confirm:(resources stringWithCRs:'''%1'' is a new module.\\create it ?' with:moduleName) 
                noLabel:'Cancel'
        ].
        answer ifFalse:[ ^ false].

        (mgr createModule:module) ifFalse:[
            self warn:(resources stringWithCRs:'Cannot create new module: ''%1''' with:moduleName) .
            ^ false.
        ]
    ].
    ^ true.
!

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:aLogInfoNil withCheck:doCheckClass
    "check a class into the source repository.
     If the argument, aLogInfoNil isNil, ask interactively for log-message.
     If doCheckClass is true, the class is checked for send of halts etc."

    |logMessage checkinInfo mgr pri resources selectorsInChangeSet initialLog|

    aClass isLoaded ifFalse:[
        self information:'cannot checkin unloaded classes (' , aClass name , ').'.
        ^ false.
    ].

    mgr := self sourceCodeManagerFor:aClass.
    mgr isNil ifTrue:[
        ^ false
    ].

    aLogInfoNil isNil ifTrue:[
        selectorsInChangeSet := ChangeSet current 
                                    select:[:aChange | aChange isMethodChange and:[aChange className = aClass name]]
                                    thenCollect:[:aChange | aChange selector].
        selectorsInChangeSet size == 1 ifTrue:[
            initialLog := 'changed ',selectorsInChangeSet first storeString.
        ].
"/        newSelectors := aClass selectors asSet.
"/        newSelectors addAll:(aClass class selectors).
"/        newSelectors size == 1 ifTrue:[
"/            initialLog := 'Added/changed #' , newSelectors first
"/        ] ifFalse:[
"/            newSelectors size > 1 ifTrue:[
"/                initialLog := 'Added/changed some methods'
"/            ]
"/        ].

        checkinInfo := self 
                        getCheckinInfoFor:aClass name 
                        initialAnswer:initialLog.
        checkinInfo isNil ifTrue:[^ false].
        logMessage := checkinInfo logMessage.
    ] ifFalse:[
        aLogInfoNil isString ifTrue:[
            "soon obsolete..."    
            logMessage := aLogInfoNil
        ] ifFalse:[ 
            checkinInfo := aLogInfoNil.
            logMessage := checkinInfo logMessage.
        ].
    ].

    resources := self classResources.

    (self classIsNotYetInRepository:aClass withManager:mgr) ifTrue:[
        (self createSourceContainerForClass:aClass) 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:[ 
            "/ mhmh - check if it has a container.
            (mgr checkForExistingContainerForClass:aClass) ifFalse:[
                (self createSourceContainerForClass:aClass) ifFalse:[
                    self warn:'Did not create/change repository container for ''' , aClass name allBold , ''''.
                    ^ false.
                ].
                freshCreated := true.
            ]
        ].

        doCheckClass value ifTrue:[
            "/ check if the class contains halts, error-sends etc.
            (self checkAndWarnAboutBadMessagesInClass:aClass checkAgainHolder:doCheckClass) 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].

                checkinState ifFalse:[
                    Transcript showCR:'checkin of ''' , aClass name , ''' failed - ', cause.
                    self warn:'checkin of ''' , aClass name allBold , ''' failed - ', cause.
                    ^ 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 an additional tag for class that has been checked in"
                        self tagClass:aClass as:(checkinInfo tag).
                    ].
                ].
            ].
            aborted ifTrue:[  |con|
                Transcript showCR:'Checkin of ''' , aClass name , ''' aborted'.

                AbortAllOperationRequest isHandled ifTrue:[
                    (Dialog 
                        confirm:(resources stringWithCRs:'Checkin of ''' , aClass name , ''' aborted.\\Cancel all ?')
                        default:false)
                    ifTrue:[
                        AbortAllOperationRequest raise.
                    ]
                ].
                ^ false.
            ].
        ].
    ].
    ^ true

    "Modified: / 25-10-2006 / 09:43:26 / 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."

    ^ self
        checkinClasses:aCollectionOfClasses 
        withInfo:aLogInfoOrNil 
        withCheck:(UserPreferences current at:#checkClassesWhenCheckingIn ifAbsent:true)
!

checkinClasses:aCollectionOfClasses withInfo:aLogInfoOrStringNil withCheck:doCheckClasses
    "check a bunch of classes into the source repository.
     If the argument, aLogInfoOrStringNil isNil, ask interactively for log-message."

    |classes allClasses checkinInfoOrString resources 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:aLogInfoOrStringNil withCheck:doCheckClasses.
    ].

    resources := self classResources.

    "ask once, for all classes"
    aLogInfoOrStringNil isNil ifTrue:[
        checkinInfoOrString := self 
                        getCheckinInfoFor:(resources string:'%1 classes to checkin' with:aCollectionOfClasses size)
                        initialAnswer:nil
                        withQuickOption:true.
        checkinInfoOrString isNil ifTrue:[^ self].
    ] ifFalse:[
        checkinInfoOrString := aLogInfoOrStringNil.
    ].

    allClasses := classes.    
    checkinInfoOrString quickCheckIn ifTrue:[
        classes := classes select:[:aClass | ChangeSet current includesChangeForClassOrMetaclassOrPrivateClassOf:aClass].
    ].

    AbortAllOperationRequest handle:[:ex |
        ex return
    ] do:[
        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:doCheckClasses
                            ]
                        ].
                    ].
                ]
            ].
        ].

        (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 select:[:eachClass | (classes includes:eachClass) not].

            "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).
                ].
            ].
        ].
    ].

    "Modified: / 12-09-2006 / 13:07:49 / cg"
!

checkinExtensionMethods:aCollectionOfMethods forPackage:aPackageID withInfo:aLogInfoOrStringOrNil
    "checkin a projects extensions into the source repository.
     If the argument, aLogInfoOrStringOrNil isNil, ask interactively for log-message."

    |logMessage checkinInfo mgr pri resources module directory containerFileName s 
     methodSource methodsSortedByName|

    resources := self classResources.

    mgr := self sourceCodeManagerFor:aCollectionOfMethods first mclass.
    mgr isNil ifTrue:[
        ^ false.
    ].

    module := aPackageID asPackageId module.
    directory := aPackageID asPackageId directory.
    containerFileName := self nameOfExtensionsContainer.

    aLogInfoOrStringOrNil isNil ifTrue:[
        checkinInfo := self getCheckinInfoFor:containerFileName allBold initialAnswer:nil.
        checkinInfo isNil ifTrue:[^ false].
        logMessage := checkinInfo logMessage.
    ] ifFalse:[
        aLogInfoOrStringOrNil isString ifTrue:[
            logMessage := aLogInfoOrStringOrNil
        ] ifFalse:[
            checkinInfo := aLogInfoOrStringOrNil.
            logMessage := checkinInfo logMessage.
        ].
    ].

    (self checkForExistingModule:module using:mgr allowCreate:true) ifFalse:[^ false].
    LastModule := module.

    (self checkForExistingModule:module directory:directory using:mgr allowCreate:true) ifFalse:[^ false].
    LastPackage := directory.

    (self checkForExistingModule:module directory:directory container:containerFileName using:mgr allowCreate:true) ifFalse:[^ false].

    self activityNotification:(resources string:'Checking in %1' with:containerFileName).
    pri := Processor activePriority.
    Processor activeProcess withPriority:pri-1 to:pri
    do:[
        s := '' writeStream.
        
        s nextPutAll:'"{ Package: '''.
        s nextPutAll:aPackageID asString.
        s nextPutAll:''' }"'; cr; nextPutChunkSeparator; cr; cr.

"/        s nextPutAll:(Smalltalk timeStamp).
"/        s nextPutChunkSeparator. 
"/        s cr; cr.

        "/ sort them by name (to avoid conflict due to CVS merge)
        methodsSortedByName := aCollectionOfMethods asOrderedCollection.
        methodsSortedByName sort:[:a :b |
                                        |clsA clsB|

                                        clsA := a mclass name.
                                        clsB := b mclass name.
                                        clsA < clsB ifTrue:[
                                            true
                                        ] ifFalse:[
                                            clsA > clsB ifTrue:[
                                                false
                                            ] ifFalse:[
                                                a selector < b selector
                                            ]
                                        ]
                                  ].
        methodsSortedByName do:[:aMethod |
            aMethod mclass fileOutMethod:aMethod on:s.
            s cr.
        ].
        methodSource := s contents.

        UserInformation handle:[:ex |
            Transcript showCR:ex description.
            ex proceed.
        ] do:[
            Transcript showCR:('checking in ',containerFileName,' ...').
            (mgr 
                checkin:containerFileName
                text:methodSource
                directory:directory 
                module:module
                logMessage:logMessage
                force:false) 
            ifFalse:[
                Transcript showCR:'Checkin of ''' , containerFileName , ''' failed'.
                self warn:'Checkin of ''' , containerFileName allBold , ''' failed'.
                ^ false.
            ].
            checkinInfo notNil ifTrue:[
                |path|

                path := (module, '/', directory, '/', containerFileName).
                checkinInfo isStable ifTrue:[
                    "set stable tag for class that has been checked in"
                    self tagPath:path as:#stable using:mgr.    
                ].
                checkinInfo tagIt ifTrue:[
                    "set an additional tag for class that has been checked in"
                    self tagPath:path as:(checkinInfo tag) using:mgr.    
                ].
            ].
            mgr postCheckInExtensionsForPackage:aPackageID    
        ].
    ].
    ^ true

    "Modified: / 12-09-2006 / 14:14:49 / cg"
!

checkoutClass:aClass askForMerge:askForMerge
    "check-out a class from the source repository."

    self
        checkoutClass:aClass 
        askForRevision:true
        askForMerge:askForMerge
!

checkoutClass:aClass askForRevision:askForRevision askForMerge:askForMerge
    "check-out a class from the source repository.
     If askForRevision is false, check-out the newest version."

    |mgr resources sourceInfo
     currentClass inChangeSet
     aStream sourceToLoad currentSource rev revString
     nm msg rev2 newestRev
     containerModule containerPackage containerFile rslt
     pkg listHere listRep diffSet 
     changed onlyHere onlyInRep answer labels values singleChangeSelector
     changedClasses default versionMethodsHere versionMethodsRep changedClassDefinitions
     wasInChangeSetBefore|

    aClass isNil ifTrue:[self error:'nil class'].

    resources := self classResources.

    currentClass := aClass theNonMetaclass.

    nm := currentClass name.
    mgr := self sourceCodeManagerFor:currentClass.
    mgr isNil ifTrue:[
        ^ self
    ].

    sourceInfo := mgr sourceInfoOfClass:currentClass.
    sourceInfo notNil ifTrue:[
        currentClass package ~= Project noProjectID ifTrue:[
            containerPackage := mgr directoryFromSourceInfo:sourceInfo.
            containerModule := mgr moduleFromSourceInfo:sourceInfo.
        ].
        containerFile := mgr containerFromSourceInfo:sourceInfo.
    ].

    currentClass isLoaded ifTrue:[
        rev := currentClass binaryRevision.
        rev2 := currentClass revision.
        rev isNil ifTrue:[
            rev := rev2
        ].
        rev isNil ifTrue:[
            pkg := currentClass package.
            (pkg notNil and:[pkg ~= Project noProjectID]) ifTrue:[
                containerModule := pkg upTo:$:.
                containerPackage := pkg copyFrom:(containerModule size + 2).
            ].
            containerModule size == 0 ifTrue:[
                containerModule := (SourceCodeManagerUtilities lastModule ) ? Project current repositoryModule.
            ].
            containerPackage size == 0 ifTrue:[
                containerPackage := (SourceCodeManagerUtilities lastPackage ) ? Project current package.
            ].
            answer := self confirmWithCancel:(resources 
                                                string:'The class %3 seems to have no (valid) repository information.\\I assume you want to check it out from: %1/%2.' 
                                                with:containerModule allBold 
                                                with:containerPackage allBold
                                                with:currentClass name allBold) withCRs.
            answer isNil ifTrue:[^ self "cancelled"].
            answer ifFalse:[
                rslt := SourceCodeManagerUtilities
                    askForContainer:(resources string:'The class seems to have no repository information.\\Do you want to checkOut from an existing containers contents ?')
                    title:'Container to load from' note:nil 
                    initialModule:containerModule 
                    initialPackage:containerPackage 
                    initialFileName:(currentClass nameWithoutPrefix , '.st')
                    forNewContainer:false.

                rslt isNil ifTrue:[
                    "/ canel
                    ^ self
                ].
                containerModule := "lastModule :=" rslt at:#module.
                containerPackage := "lastPackage :=" rslt at:#package.
                containerFile := rslt at:#fileName.
            ].

"/            rslt := SourceCodeManagerUtilities
"/                askForContainer:(resources string:'The class seems to have no (valid) repository information.\\Do you want to check it out from an existing container ?')
"/                title:'Container to checkOut' note:nil 
"/                initialModule:containerModule 
"/                initialPackage:containerPackage
"/                initialFileName:(currentClass name , '.st').
"/                forNewContainer:false.
"/            rslt isNil ifTrue:[^ self].
            "/ self warn:(resources string:'Class %1 seems to be not yet in the repository' with:currentClass name allBold).
            "/ ^ self
        ].
    ].

    "/
    "/ class in repository - ask for revision
    "/
"/    newestRev := mgr newestRevisionOf:currentClass.
    newestRev := mgr newestRevisionInFile:containerFile directory:containerPackage module:containerModule.
    askForRevision ifFalse:[
        rev := newestRev ? ''
    ] ifTrue:[
        msg := resources string:'CheckOut which revision of ''%1'': (empty for newest)' with:nm allBold.
        rev notNil ifTrue:[
            msg := msg , '\\' , (resources string:'Current ''%1'' is based upon rev %2.'
                                           with:nm allBold with:rev).
            (rev2 notNil and:[rev2 ~= rev]) ifTrue:[
                msg := msg , '\' , (resources string:'And has been checked into the repository as %1.'
                                               with:rev2)
            ]
        ].
        newestRev notNil ifTrue:[
            msg := msg , '\' , (resources string:'Newest in repository is %1.'
                                           with:newestRev)
        ].

        rev := SourceCodeManagerUtilities
                    askForExistingRevision:msg 
                    title:'CheckOut from repository' 
                    class:currentClass.
        rev isNil ifTrue:[
            ^ self   "/ canceled
        ].
    ].

    rev withoutSpaces isEmpty ifTrue:[
        msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
        "/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
        aStream := mgr getSourceStreamFor:currentClass revision:newestRev.
        revString := '(newest: ' , (newestRev ? '???') , ')'.
    ] ifFalse:[
        msg := 'extracting previous %1'.
"/        aStream := mgr getSourceStreamFor:currentClass revision:rev.
"/        revString := rev
        aStream := mgr  
            streamForClass:currentClass
            fileName:containerFile 
            revision:rev 
            directory:containerPackage 
            module:containerModule
            cache:true.
    ].

    aStream isNil ifTrue:[
        self warn:(resources string:'Could not extract source of %1 from repository' with:aClass name allBold).
        ^ self
    ].
    aStream class readErrorSignal handle:[:ex |
        self warn:('Read error while reading extracted source\\' , ex description) withCRs.
        aStream close.
        ^ self
    ] do:[
        sourceToLoad := aStream contents asString.
    ].
    aStream close.

    wasInChangeSetBefore := ChangeSet current includesChangeForClass:currentClass.

    currentClass isLoaded ifFalse:[
        rev = newestRev ifTrue:[
            currentClass autoload.
        ] ifFalse:[
            sourceToLoad readStream fileIn.
        ].
        wasInChangeSetBefore ifFalse:[
            ChangeSet current condenseChangesForClass:currentClass.
        ].
        ^ self.
    ].

    inChangeSet := ChangeSet current includesChangeForClassOrMetaclassOrPrivateClassOf:aClass.

    self activityNotification:'generating current source...'.

    currentSource := self sourceCodeOfClass:currentClass.

    self activityNotification:'comparing...'.

    sourceToLoad = currentSource ifTrue:[
        "/ make all methods belong to the classes project
        self setPackageOfAllMethodsIn:aClass to:aClass package.
        inChangeSet ifTrue:[
            rev = newestRev ifTrue:[
                (wasInChangeSetBefore not
                or:[ self confirm:(resources 
                                stringWithCRs:'%1 is up-to-date.\\Remove entries for %1 from changeSet ?'
                                with:aClass name)]) 
                ifTrue:[
                    ChangeSet current condenseChangesForClass:aClass.
                ].
            ].
        ].
        ^ self.
    ].

    self activityNotification:'generating diffSet...'.
    listHere := ChangeSet fromStream:(currentSource readStream).
    listRep := ChangeSet fromStream:(sourceToLoad readStream).

    versionMethodsHere := listHere select:[:change | (change isMethodChange 
                                           and:[change selector == #version
                                           and:[change changeClass isMeta]])].

    versionMethodsRep := listRep select:[:change | (change isMethodChange 
                                           and:[change selector == #version
                                           and:[change changeClass isMeta]])].

    "/ compare all but the version methods
    listHere := listHere select:[:change | (change isMethodChange 
                                           and:[change selector == #version
                                           and:[change changeClass isMeta]]) not].
    listRep := listRep select:[:change | (change isMethodChange 
                                           and:[change selector == #version
                                           and:[change changeClass isMeta]]) not].

    diffSet := listHere diffSetsAgainst:listRep.
    changed := diffSet changed.
    onlyHere := diffSet onlyInReceiver.
    onlyInRep := diffSet onlyInArg.

    changedClassDefinitions := changed select:[:eachChangePair | eachChangePair first isClassDefinitionChange]. 
    changed := changed reject:[:eachChangePair | eachChangePair first isClassDefinitionChange]. 

    labels := #('Cancel' 'Merge' 'Load'). 
    values := #(nil #merge #load). 
    default := askForRevision 
                    ifTrue:[3. "i.e. load"]
                    ifFalse:[2. "i.e. merge"].

    msg := 'About to load ''%4''.\\'.
    onlyInRep size > 0 ifTrue:[
        msg := msg , 'The repositories version contains %1 method(s) which are not in your current class.\'.
    ].
    onlyHere size > 0 ifTrue:[
        onlyInRep size > 0 ifTrue:[
            msg := msg , 'And there '.
        ] ifFalse:[
            msg := msg , 'There '.
        ].
        msg := msg , 'are %2 methods in your current class, which are not in the repository.\'.
    ].
    changed size > 0 ifTrue:[
        changed size == 1 ifTrue:[
            msg := msg , 'The ''%6''-method is different (present in both).\\'.
            singleChangeSelector := changed first first selector allBold
        ] ifFalse:[
            msg := msg , '%3 methods are different (present in both).\\'.
        ]
    ].
    changedClassDefinitions size > 0 ifTrue:[
        changedClassDefinitions size == 1 ifTrue:[
            msg := msg , 'The class definition is different.\\'.
        ] ifFalse:[
            msg := msg , '%5 class definitions are different.\\'.
        ]
    ].

    onlyHere isEmpty ifTrue:[
        onlyInRep isEmpty ifTrue:[
            (changed isEmpty and:[changedClassDefinitions isEmpty]) ifTrue:[
                "/ make all methods belong to the classes project
                versionMethodsRep size == 1 ifTrue:[
"/                    (self confirm:(resources string:'Versions are identical: %1\\Update the version-ID ?' with:aClass name) withCRs) ifTrue:[
                        versionMethodsRep first apply.
"/                    ]
                ].
                self setPackageOfAllMethodsIn:aClass to:aClass package.
                ^ self
            ].
            inChangeSet ifTrue:[
                msg := msg , '\Attention:\Load will undo your changes made to ''%4'' (if any were made).'.
            ].
            labels := #('Cancel' 'Load'). 
            values := #(nil #load). 
            default := askForRevision 
                            ifTrue:[2. "i.e. load"]
                            ifFalse:[1. "i.e. cancel"].
            default := 2. 
        ] ifFalse:[
            changed isEmpty ifTrue:[
                msg := msg , '\Attention:\Load will load methods which are not present in ''%4''.'.
                labels := #('Cancel' 'Load'). 
                values := #(nil #load). 
                default := askForRevision 
                                ifTrue:[2. "i.e. load"]
                                ifFalse:[1. "i.e. cancel"].
                default := 2. 
            ] ifFalse:[
                inChangeSet ifTrue:[
                    msg := msg , '\Attention:\Load will undo your changes made to ''%4'' (if any were made);'.
                ].
                msg := msg , '\Merge will only load methods which are not present in ''%4'' (i.e. undo removals but preserve changes).'.
            ].
        ]
    ] ifFalse:[
        onlyInRep isEmpty ifTrue:[
            inChangeSet ifTrue:[
                msg := msg , '\Attention:\Load will undo your changes made to ''%4'' (if any were made),'.
                msg := msg , '\and remove added methods which are not present in the repository version.'.
            ].
            labels := #('Cancel' 'Load'). 
            values := #(nil #load). 
            default := askForRevision 
                            ifTrue:[2. "i.e. load"]
                            ifFalse:[1. "i.e. cancel"].
            default := 2. 
        ] ifFalse:[
            inChangeSet ifTrue:[
                msg := msg , '\Attention:\Load will undo your changes made to ''%4'' (if any were made);'.
                msg := msg , '\Merge will only load methods which are not present in ''%4'' (i.e. undo removals but preserve changes).'.
            ]
        ]
    ].

    msg := msg bindWith:onlyInRep size printString 
               with:onlyHere size printString 
               with:changed size printString
               with:aClass name allBold
               with:changedClassDefinitions size printString
               with:singleChangeSelector.

    answer := (Dialog confirmWithCancel:msg withCRs
           labels:(resources array:labels)
           values:values 
           default:default).
    answer isNil ifTrue:[^ self].

    self activityNotification:'updating...'.
    changedClasses := IdentitySet new.

"/    Class withoutUpdatingChangesDo:[
        answer == #load ifTrue:[
            changedClassDefinitions do:[:eachChangeArr | "apply this change (go to rep-version)"
                                         |cHere cRep| 
                                         cHere := eachChangeArr at:1.
                                         cRep := eachChangeArr at:2.
                                         cRep apply.
                                         cRep isMethodChange ifTrue:[
                                             cRep changeMethod setPackage:(cRep changeClass package).
                                             changedClasses add:cRep changeClass.
                                         ]
                       ].
        ].
        onlyInRep do:[:eachChange | "apply this change (method only present in rep-version)"
                                     eachChange apply.
                                     eachChange isMethodChange ifTrue:[
                                         eachChange changeMethod setPackage:(eachChange changeClass package).
                                         changedClasses add:eachChange changeClass.   
                                     ]
                     ].
        answer == #load ifTrue:[
            onlyHere do:[:eachChange |   "remove this change (method not present in rep-version)"
                                         |cClass cSel|
                                         eachChange isMethodChange ifTrue:[
                                             cClass := eachChange changeClass.
                                             cSel := eachChange selector.
                                             cClass removeSelector:cSel.
                                         ]
                        ].
            changed do:[:eachChangeArr | "apply this change (go to rep-version)"
                                         |cHere cRep| 
                                         cHere := eachChangeArr at:1.
                                         cRep := eachChangeArr at:2.
                                         cRep apply.
                                         cRep isMethodChange ifTrue:[
                                             cRep changeMethod setPackage:(cRep changeClass package).
                                             changedClasses add:cRep changeClass.
                                         ]
                       ].
            "/ make all methods belong to the classes project
            self setPackageOfAllMethodsIn:aClass to:aClass package.
            versionMethodsRep size == 1 ifTrue:[
                versionMethodsRep first apply.
                self setPackageOfAllMethodsIn:aClass to:aClass package.
            ] ifFalse:[
                self error:'too many version methods'.
            ].
        ].
"/    ].

    answer == #load ifTrue:[
        inChangeSet := ChangeSet current includesChangeForClassOrMetaclassOrPrivateClassOf:aClass.
        inChangeSet ifTrue:[
            rev = newestRev ifTrue:[
                (wasInChangeSetBefore not
                or:[ self confirm:(resources 
                                stringWithCRs:'%1 is now up-to-date.\\Remove entries for %1 from changeSet ?'
                                with:aClass name)]) 
                ifTrue:[
                    ChangeSet current condenseChangesForClass:aClass.
                ].
            ].
        ].
    ].

    changedClasses do:[:eachClass |
         eachClass changed:#projectOrganization.
    ].
    Smalltalk changed:#projectOrganization.

    "Modified: / 07-02-2001 / 18:18:32 / ps"
    "Modified: / 23-10-2006 / 10:35:07 / cg"
!

checkoutExtensionMethodsForPackage:packageToCheckOut askForRevision:askForRevision askForMerge:askForMerge using:aSourceCodeManager
    "check-out a class from the source repository.
     If askForRevision is false, check-out the newest version."

    |resources 
     inChangeSet extensionMethods
     rev msg
     listHere listRep diffSet 
     changed onlyHere onlyInRep answer labels values singleChangeSelector
     changedClasses default |

    listRep := self changeSetForExtensionMethodsForPackage:packageToCheckOut askForRevision:askForRevision using:aSourceCodeManager.
    listRep isNil ifTrue:[ ^self ].

    resources := self classResources.

    self activityNotification:'generating diffSet...'.

    extensionMethods := OrderedCollection new.
    Smalltalk allClassesDo:[:aClass | |owner classPackage|
        "/ individual methods ...
        aClass isMeta ifFalse:[
            (aClass package ~= packageToCheckOut) ifTrue:[
                aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
                    "/ methods in this project ...
                    (mthd package = packageToCheckOut) ifTrue:[
                        "/ ... whose class is not in the ckechIn-set
                        extensionMethods add:mthd
                    ]
                ].
            ].
        ].
    ].
    listHere := ChangeSet forExistingMethods:extensionMethods.

    inChangeSet := listRep contains:[:someChange |
                            |cClass cSel|

                            someChange isMethodChange ifTrue:[
                                cClass := someChange changeClass.
                                cSel := someChange selector.
                                ChangeSet current includesChangeForClass:cClass selector:cSel
                            ]
                    ].

    diffSet := listHere diffSetsAgainst:listRep.
    changed := diffSet changed.
    onlyHere := diffSet onlyInReceiver.
    onlyInRep := diffSet onlyInArg.

    labels := #('Cancel' 'Merge' 'Load'). 
    values := #(nil #merge #load). 
    default := askForRevision 
                    ifTrue:[3. "i.e. load"]
                    ifFalse:[2. "i.e. merge"].

    msg := 'About to load extensions for ''%5''.\\'.
    onlyInRep size > 0 ifTrue:[
        msg := msg , 'The repositories version contains %1 extension method(s) which are not in your current image.\'.
    ].
    onlyHere size > 0 ifTrue:[
        onlyInRep size > 0 ifTrue:[
            msg := msg , 'And there '.
        ] ifFalse:[
            msg := msg , 'There '.
        ].
        msg := msg , 'are %2 extension methods in your current image, which are not in the repository.\'.
    ].
    changed size > 0 ifTrue:[
        changed size == 1 ifTrue:[
            msg := msg , 'The ''%5''-method is different (present in both).\\'.
            singleChangeSelector := changed first first selector allBold
        ] ifFalse:[
            msg := msg , '%3 methods are different (present in both).\\'.
        ]
    ].

    onlyHere isEmpty ifTrue:[
        onlyInRep isEmpty ifTrue:[
            (changed isEmpty) ifTrue:[
                listRep do:[:eachChange |
                    eachChange changeMethod setPackage:packageToCheckOut.
                ].
                ^ self
            ].
            inChangeSet ifTrue:[
                msg := msg , '\Attention:\Load may undo any changes made to on of the extension methods (if any were made).'.
            ].
            labels := #('Cancel' 'Load'). 
            values := #(nil #load). 
            default := askForRevision 
                            ifTrue:[2. "i.e. load"]
                            ifFalse:[1. "i.e. cancel"].
        ] ifFalse:[
            changed isEmpty ifTrue:[
                msg := msg , '\Attention:\Load will load methods which are not present in the image.'.
                labels := #('Cancel' 'Load'). 
                values := #(nil #load). 
                default := askForRevision 
                                ifTrue:[2. "i.e. load"]
                                ifFalse:[1. "i.e. cancel"].
            ] ifFalse:[
                inChangeSet ifTrue:[
                    msg := msg , '\Attention:\Load will undo your changes made to the image (if any were made);'.
                ].
                msg := msg , '\Merge will only load methods which are not present in the image (i.e. undo removals but preserve changes).'.
            ].
        ]
    ] ifFalse:[
        onlyInRep isEmpty ifTrue:[
            inChangeSet ifTrue:[
                msg := msg , '\Attention:\Load will undo your changes made to the image (if any were made),'.
                msg := msg , '\and remove added methods which are not present in the repository version.'.
            ].
            labels := #('Cancel' 'Load'). 
            values := #(nil #load). 
            default := askForRevision 
                            ifTrue:[2. "i.e. load"]
                            ifFalse:[1. "i.e. cancel"].
        ] ifFalse:[
            inChangeSet ifTrue:[
                msg := msg , '\Attention:\Load will undo your changes made to the image (if any were made);'.
                msg := msg , '\Merge will only load methods which are not present in the image (i.e. undo removals but preserve changes).'.
            ]
        ]
    ].

    msg := msg bindWith:onlyInRep size printString 
               with:onlyHere size printString 
               with:changed size printString
               with:singleChangeSelector
               with:packageToCheckOut allBold.

    answer := (Dialog confirmWithCancel:msg withCRs
           labels:(resources array:labels)
           values:values 
           default:default).
    answer isNil ifTrue:[^ self].

    self activityNotification:'updating...'.
    changedClasses := IdentitySet new.

"/    Class withoutUpdatingChangesDo:[
        onlyInRep do:[:eachChange | "apply this change (method only present in rep-version)"
                                     Class withoutUpdatingChangeSetDo:[ eachChange apply ].

                                     eachChange changeMethod setPackage:packageToCheckOut.
                                     changedClasses add:eachChange changeClass.   
                     ].
        answer == #load ifTrue:[
            onlyHere do:[:eachChange |   "remove this change (method not present in rep-version)"
                                         |cClass cSel|

                                         cClass := eachChange changeClass.
                                         cSel := eachChange selector.
                                         Class withoutUpdatingChangeSetDo:[ cClass removeSelector:cSel ].
                        ].
            changed do:[:eachChangeArr | "apply this change (go to rep-version)"
                                         |cHere cRep| 
                                         cHere := eachChangeArr at:1.
                                         cRep := eachChangeArr at:2.
                                         Class withoutUpdatingChangeSetDo:[ cRep apply ].

                                         cRep changeMethod setPackage:packageToCheckOut.
                                         changedClasses add:cRep changeClass.
                       ].
        ].
"/    ].
    changedClasses do:[:eachClass |
         eachClass changed:#projectOrganization.
    ].
    Smalltalk changed:#projectOrganization.

    "Modified: / 07-02-2001 / 18:18:32 / ps"
    "Created: / 10-08-2006 / 18:57:30 / cg"
    "Modified: / 09-10-2006 / 13:06:43 / cg"
!

compareClassWithRepository:aClass
    "open a diff-textView comparing the current (in-image) version
     against its orgiginal version found in the repository."

    self compareClassWithRepository:aClass askForRevision:true

    "
      self compareClassWithRepository:Array
    "
!

compareClassWithRepository:aClass askForRevision:askForRevision
    "open a diff-textView comparing the current (in-image) version
     against its orgiginal version found in the repository."

    |classToCompare resources brwsr
     aStream comparedSource currentSource rev revString thisRevString mgr
     nm msg revisionInClass newestRev versionsAreTheSame|

    resources := self classResources.

    classToCompare := aClass theNonMetaclass.

    nm := classToCompare name.
    mgr := self sourceCodeManagerFor:classToCompare.
    mgr isNil ifTrue:[
        ^ self
    ].
    rev := classToCompare binaryRevision.
    revisionInClass := classToCompare revision.
    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)
        ifFalse:[
            ^ self
        ]
    ].

    "/
    "/ class in repository - ask for revision
    "/
    newestRev := mgr newestRevisionOf:classToCompare.
    askForRevision ifTrue:[
        msg := resources string:'Compare to revision: (empty for newest)'.
        rev notNil ifTrue:[
            msg := msg , '\\' , (resources string:'Current %1 is based upon rev %2.'
                                           with:nm allBold with:rev).
            (revisionInClass notNil and:[revisionInClass ~= rev]) ifTrue:[
                msg := msg , '\' , (resources string:'And has been checked into the repository as %1.'
                                               with:revisionInClass)
            ]
        ].
        newestRev notNil ifTrue:[
            msg := msg , '\' , (resources string:'Newest in reporitory is %1.'
                                           with:newestRev)
        ].

        rev := SourceCodeManagerUtilities
                    askForExistingRevision:msg 
                    title:'Compare with repository' 
                    class:classToCompare.
    ] ifFalse:[
        rev := newestRev.
    ].

    rev notNil ifTrue:[
        rev withoutSpaces isEmpty ifTrue:[
            msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
            "/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
            aStream := mgr getSourceStreamFor:classToCompare revision:newestRev.
            revString := '(newest: ' , (newestRev ? '???') , ')'.
        ] ifFalse:[
            msg := 'extracting previous %1'.
            aStream := mgr getSourceStreamFor:classToCompare revision:rev.
            revString := rev
        ].

        aStream isNil ifTrue:[
            self warn:'could not extract source from repository'.
            ^ self
        ].
        aStream class readErrorSignal handle:[:ex |
            self warn:('read error while reading extracted source\\' , ex description) withCRs.
            aStream close.
            ^ self
        ] do:[
            comparedSource := aStream contents asString.
        ].
        aStream close.

        self activityNotification:'generating current source...'.

        currentSource := self sourceCodeOfClass:classToCompare.

        self activityNotification:'comparing...'.

        versionsAreTheSame := false.
        comparedSource = currentSource ifTrue:[
            versionsAreTheSame := true.
        ] ifFalse:[
            thisRevString := revisionInClass ? 'no revision'.

            revString = '(newest)' ifTrue:[
                (rev := mgr newestRevisionOf:classToCompare) notNil ifTrue:[
                    revString := '(newest is ' , rev , ')'
                ]
            ].

            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].

            versionsAreTheSame ifFalse:[
                brwsr classChangeSet 
                    classBeingCompared:classToCompare;
                    versionA:rev;
                    versionB:rev , 'mod'.
            ].
        ].

        versionsAreTheSame ifTrue:[
            (ChangeSet current includesChangeForClassOrMetaclassOrPrivateClassOf:classToCompare) ifTrue:[
                (self confirm:(resources 
                                stringWithCRs:'Versions of %1 are identical.\\Remove entries from changeSet ?'
                                with:classToCompare name allBold)) ifTrue:[
                    ChangeSet current condenseChangesForClass:classToCompare.
                ].
            ] ifFalse:[
                self information:'Versions are identical.'.
                ChangeSet current unrememberChangedClasses.
            ].
            revisionInClass isNil ifTrue:[
                (Dialog confirm:'Update (Fix) the classes Revision Info ?' withCRs)
                ifTrue:[
                    |newString root|

                    newString := mgr updatedRevisionStringOf:aClass forRevision:rev with:aClass revisionString.
                    newString isNil ifTrue:[
                        root := mgr getCVSROOTForModule:(aClass package upTo:$:).
                        root := mgr repositoryTopDirectoryFromCVSRoot:root.
                        newString := '$', 'Header: ',(root copyReplaceAll: $: with:$/ ),'/'
                                     ,(Smalltalk fileNameForClass:aClass),'.st,v ',rev
                                     ,(Date today printStringFormat:'%y/%m/%d'),' '
                                     ,(Time now printStringFormat:'%h/%m/%s'),' '
                                     ,(OperatingSystem getLoginName),' Exp $'.
                    ].
                    aClass updateVersionMethodFor:newString.
                ]
            ].
        ].
    ].

    "
      self compareClassWithRepository:Array
    "

    "Modified: / 13-10-2006 / 01:02:16 / cg"
!

compareProjectWithRepository:aProject
    |classesInImage filesInImage module directory perProjectInfo 
     classesNotInRepository filesNotInImage classesDeletedInRepository
     classesModifiedInImage classesNotReallyModified classesReallyModified classesModifiedInRepository 
     classesDeletedInImage classesAddedInImage
     extensionsInImage extensionsInRepository extensionDiffs
     anyDifference box doRemove doCleanup classDefs changeSets filePerClassDefintion
     classesToCheckIn resources diffSet def autoloadedFilesNotInImage|

    resources := self classResources.

    module := aProject asPackageId module.
    directory := aProject asPackageId directory.
    perProjectInfo := SourceCodeManager newestRevisionsInModule:module directory:directory.
    perProjectInfo := perProjectInfo ? #().
    perProjectInfo := perProjectInfo select:[:info | info key asFilename hasSuffix:'st'].
    perProjectInfo := Dictionary withAssociations:perProjectInfo.

    classesInImage := Smalltalk allClassesInPackage:aProject.
    classesInImage := classesInImage reject:[:cls | cls isPrivate].
    filesInImage := (classesInImage collect:[:cls | cls classBaseFilename]) asSet.
    "/ any differences ?
    classesNotInRepository := classesInImage reject:[:cls | (perProjectInfo includesKey:cls classBaseFilename)].
    classesDeletedInRepository := classesInImage select:[:cls | (perProjectInfo at:cls classBaseFilename ifAbsent:nil) == #deleted].
    perProjectInfo := perProjectInfo reject:[:v | v == #deleted].
    filesNotInImage := perProjectInfo keys reject:[:file | (filesInImage includes:file)].
    filesNotInImage remove:'extensions.st' ifAbsent:[].

    classesModifiedInImage := classesInImage select:[:cls |ChangeSet current includesChangeForClassOrMetaclass:cls].
    classesModifiedInImage := classesModifiedInImage \ classesNotInRepository.

    classesModifiedInRepository := classesInImage select:[:cls | |v|
                                                    v := (perProjectInfo at:cls classBaseFilename ifAbsent:nil).
                                                    v notNil and:[ cls isLoaded and:[ v > cls revision ]]].

    "/ stupid: as we do not have any revision information for extensions (sigh);
    "/ we must checkout and look at the extension.st contents, to see if it has changed.

    extensionsInImage := OrderedCollection new.
    Smalltalk allClasses do:[:eachClass |
        extensionsInImage addAll:(eachClass extensionsFrom:aProject) 
    ].
    extensionsInImage := ChangeSet forExistingMethods:extensionsInImage.

    [
        |s|

        s := SourceCodeManager
            streamForClass:nil fileName:'extensions.st' revision:#newest directory:directory module:module cache:true.
        s isNil ifTrue:[
            extensionsInRepository := ChangeSet new.
        ] ifFalse:[
            extensionsInRepository := ChangeSet fromStream:s.
            s close.
        ].
    ] value.
    extensionDiffs := extensionsInRepository diffSetsAgainst:extensionsInImage.

    diffSet := extensionDiffs copy.

    "/ we could do the same as above for each class.
    "/ however - as we do have change-info and revision info, we can avoid checking out
    "/ for all classes which are not changed and which have the same version info.

    classesModifiedInImage notEmpty ifTrue:[
        classesReallyModified :=
            classesModifiedInImage select:[:eachChangedClass |
                |currentVersion repositoryVersion s stFile diffs|

                stFile := eachChangedClass classBaseFilename.
                s := SourceCodeManager
                    streamForClass:nil fileName:stFile revision:#newest directory:directory module:module cache:true.
                repositoryVersion := ChangeSet fromStream:s.
                s close.

                currentVersion := ChangeSet forExistingClass:eachChangedClass.
                diffs := repositoryVersion diffSetsAgainst:currentVersion .
                diffSet addDiffSet:diffs.
                diffs notEmpty
            ].

        classesNotReallyModified := classesModifiedInImage \ classesReallyModified.
    ].

    filesNotInImage notEmpty ifTrue:[
        "/ first, check if these are autoloaded classes which have NOT been installed
        "/ (for example, due to a --quick argument during startup)
        autoloadedFilesNotInImage := OrderedCollection new.

        def := ProjectDefinition definitionClassForPackage:aProject createIfAbsent:false projectType:nil.
        def notNil ifTrue:[
            def classNamesAndAttributesDo:[:eachClassname :eachAttributes | 
                |cls eachFileName isAutoload|

                cls := Smalltalk classNamed:eachClassname.
                cls isNil ifTrue:[
                    isAutoload := eachAttributes includes:#autoload.
                    isAutoload ifTrue:[
                        eachFileName := Smalltalk fileNameForClass:eachClassname.
                        autoloadedFilesNotInImage add:(eachFileName , '.st')
                    ]
                ]
            ].
        ].

        (filesNotInImage \ autoloadedFilesNotInImage) do:[:eachSTFile |
            |s chgSet classDefinitions|

            s := SourceCodeManager
                streamForClass:nil fileName:eachSTFile revision:#newest directory:directory module:module cache:true.
            chgSet := ChangeSet fromStream:s.
            s close.

            diffSet onlyInReceiver addAll:chgSet
        ].
    ].

    classesModifiedInRepository notEmpty ifTrue:[
        classesModifiedInRepository do:[:eachClass|
            |s diffs repositoryVersion currentVersion|

            s := SourceCodeManager
                streamForClass:eachClass fileName:nil revision:#newest directory:directory module:module cache:true.
            repositoryVersion := ChangeSet fromStream:s.
            s close.

            currentVersion := ChangeSet forExistingClass:eachClass.
            diffs := repositoryVersion diffSetsAgainst:currentVersion .
            diffSet addDiffSet:diffs.
        ].
    ].
    classesDeletedInRepository notEmpty ifTrue:[
self halt.
    ].
    classesNotInRepository notEmpty ifTrue:[
        "/ if there are no changeSet entries for those classes, they seem to be
        "/ no longer in the repository (possibly moved ?)
        "/ If there are entries, these might have been added in the image and need a check-in

        classesAddedInImage := classesNotInRepository \ classesDeletedInRepository.
        classesAddedInImage do:[:eachAddedClass |
            |currentVersion|

            currentVersion := ChangeSet forExistingClass:eachAddedClass.
            diffSet onlyInArg addAll:currentVersion.
        ].
    ].

    diffSet isEmpty ifTrue:[
        "/ Dialog information:(resources string:'%1 is up-to-date.' with:eachProject allBold).
        Transcript showCR:('%1 is up-to-date.' bindWith:aProject allBold).
        (ChangeSet current includesChangeForPackage:aProject) ifTrue:[
            (Dialog confirm:('%1 is up-to-date.\\Cleanup ChangeSet ?' bindWith:aProject allBold) withCRs) ifTrue:[
                ChangeSet current condenseChangesForPackage:aProject.
            ].
        ].
        ^ self.
    ].

    classesNotReallyModified notEmptyOrNil ifTrue:[
self halt.
        doCleanup := false.
        box := Dialog
            forRequestText:(resources 
                                stringWithCRs:'The following classes from %1 are equal to the repository version.\\Remove entries from the changeSet ?'
                                with:aProject allBold) 
            editViewClass:ListView
            lines:10 columns:20 
            initialAnswer:nil model:nil
            setupWith:
               [:v :d | 
                        |removeButton|

                        v list:classesNotReallyModified.
                        removeButton := Button label:(resources string:'Cleanup ChangeSet').
                        removeButton action:[ doCleanup := true. box okPressed. ].
                        d addButton:removeButton after:(d okButton).
                        d okButton label:(resources string:'Continue').
                        d okButton isReturnButton:false.
                        removeButton isReturnButton:true.
               ].
        box open.
        box accepted ifFalse:[
            ^ self
        ].
        doCleanup ifTrue:[
            classesNotReallyModified do:[
                ChangeSet current condenseChangesForClass:classesNotReallyModified.
            ]
        ].
    ].

    VersionDiffBrowser 
        openOnDiffSet:diffSet 
        labelA:'Repository' 
        labelB:'Image' 
        title:('Differences of %1' bindWith:aProject).

    "Created: / 12-10-2006 / 21:44:54 / cg"
    "Modified: / 25-10-2006 / 18:08:21 / cg"
!

createSourceContainerForClass:aClass
    "let user specify the source-repository values for aClass"

    |resources|

    resources := self classResources.
    ^ self 
        defineSourceContainerForClass:aClass 
        title:(resources string:'Repository information for %1' with:aClass name)
        text:(resources string:'Create new repository container for ''%1''' with:aClass name allBold)
        createDirectories:true
        createContainer:true.
!

defineSourceContainerForClass:aClass title:title text:boxText createDirectories:createDirs createContainer:createContainer
    "let user specify the source-repository values for aClass"

    | className
     oldModule oldPackage oldFileName
     module directory fileName nameSpace nameSpacePrefix
     info project nm mgr creatingNew msg 
     answer doCheckinWithoutAsking forceCheckIn resources rslt note
     requiredPackage|

    resources := self classResources.
    aClass isLoaded ifFalse:[
        self warn:(resources string:'Please load the %1-class first' with:aClass name).
        ^ false.
    ].

    className := aClass name.

    aClass isProjectDefinition ifTrue:[
        "/ no way - their package is already known and fix.
        module := aClass module.
        directory := aClass moduleDirectory.
    ] ifFalse:[
        "/
        "/ defaults, if nothing at all is known
        "/
        (module := LastModule) isNil ifTrue:[
            module := (OperatingSystem getLoginName).
        ].
        (directory := LastPackage) isNil ifTrue:[
            directory := 'private'.
        ].
    ].

    "/
    "/ try to extract some useful defaults from the current project
    "/
    (Project notNil and:[(project := Project current) notNil]) ifTrue:[
        directory isNil ifTrue:[
            (nm := project repositoryDirectory) isNil ifTrue:[
                nm := project name
            ].
            directory := nm.
        ].
        module isNil ifTrue:[
            (nm := project repositoryModule) notNil ifTrue:[
                module := nm
            ]
        ].
    ].

    "/
    "/ 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 := mgr sourceInfoOfClass:aClass.
    info notNil ifTrue:[
        true "module ~= LastModule" ifTrue:[
            (info includesKey:#module) ifTrue:[
                module := (info at:#module).
            ].
        ].
"/        true "package ~= LastPackage" ifTrue:[
"/            (info includesKey:#directory) ifTrue:[
"/                package := (info at:#directory).
"/            ].
"/        ].
        fileName := mgr containerFromSourceInfo:info.
        (nameSpace := aClass nameSpace) ~~ Smalltalk ifTrue:[
            nameSpacePrefix := nameSpace name , '::'.
            (fileName startsWith:nameSpacePrefix) ifTrue:[
                fileName := fileName copyFrom:(nameSpacePrefix size + 1).
            ]
        ].
"/        (info includesKey:#fileName) ifTrue:[
"/            fileName := (info at:#fileName).
"/        ] ifFalse:[
"/            (info includesKey:#expectedFileName) ifTrue:[
"/                fileName := (info at:#expectedFileName).
"/            ] ifFalse:[
"/                (info includesKey:#classFileNameBase) ifTrue:[
"/                    fileName := (info at:#classFileNameBase) , '.st'.
"/                ]
"/            ]
"/        ]
    ].

    fileName isNil ifTrue:[
        fileName := (Smalltalk fileNameForClass:aClass) , '.st'.
    ].

    OperatingSystem isMSDOSlike ifTrue:[
        module replaceAll:$\ with:$/.
        directory replaceAll:$\ with:$/.
    ].

    "/
    "/ check for conflicts (i.e. if such a container already exists) ...
    "/
    doCheckinWithoutAsking := false.
"/false ifTrue:[
"/    (mgr checkForExistingContainer:fileName inModule:module directory:directory) ifTrue:[
"/        answer := Dialog confirmWithCancel:(resources 
"/                            string:'About to change the source container.
"/
"/Notice: there is a container for %1 in:
"/
"/    %2 / %3 / %4
"/
"/Do you want to change it or check right into that container ?'
"/                            with:className
"/                            with:module
"/                            with:directory
"/                            with:fileName)
"/                labels:(resources array:#('Cancel' 'Check in' 'Change')).
"/        answer isNil ifTrue:[AbortSignal raise].
"/        answer ifTrue:[
"/            doCheckinWithoutAsking := false.
"/            oldModule := module.
"/            oldPackage := directory.
"/            oldFileName := fileName
"/        ] ifFalse:[
"/            doCheckinWithoutAsking := true.
"/            creatingNew := false.
"/        ].
"/    ].
"/].
    doCheckinWithoutAsking ifFalse:[
        "/
        "/ open a dialog for this
        "/
        (mgr checkForExistingContainer:fileName inModule:module directory:directory) ifFalse:[
            note := 'Notice: class seems to have no container yet.'.
            creatingNew := true.
        ] ifTrue:[
            creatingNew := false.
        ].

        rslt := self 
                askForContainer:boxText title:title note:note
                initialModule:module initialPackage:directory initialFileName:fileName
                forNewContainer:true.        

        rslt isNil ifTrue:[
            ^ false
        ].

        module := rslt at:#module.
        directory := rslt at:#package.
        fileName := rslt at:#fileName.
    ].

    (fileName endsWith:',v') ifTrue:[
        fileName := fileName copyWithoutLast:2
    ].
    (fileName endsWith:'.st') ifFalse:[
        fileName := fileName , '.st'
    ].

    "/ we require the packageID to be <module>:<container-dir>
    "/ check for this ...

    requiredPackage := ((module ? '') , ':' , (directory ? '')) asSymbol.
    requiredPackage ~= aClass package ifTrue:[
"/        doCheckinWithoutAsking ifFalse:[
"/            (self confirm:'Change the classes packageID to: ''', requiredPackage , ''' ?')
"/            ifFalse:[
"/                ^ false
"/            ]
"/        ].
        aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | mthd setPackage:requiredPackage].
        aClass package:requiredPackage.
    ].

    info := aClass revisionInfo.
    info notNil ifTrue:[
        (info includesKey:#repositoryPathName) ifFalse:[
            info := nil
        ]
    ].
    info isNil ifTrue:[
        true "doCheckinWithoutAsking" ifFalse:[
            answer := Dialog 
                 confirmWithCancel:(resources string:'%1 does not have any (usable) revision info (#version method)\\Shall I create one ?' with:className) withCRs
                 labels:(resources array:#( 'Cancel' 'No' 'Yes')).
            answer isNil ifTrue:[^ false].
        ] ifTrue:[
            answer := true.
        ].
        answer ifTrue:[
            aClass updateVersionMethodFor:(mgr initialRevisionStringFor:aClass 
                                               inModule:module 
                                               directory:directory 
                                               container:fileName).
        ].
    ].

    (self checkForExistingModule:module using:mgr allowCreate:(createDirs or:[creatingNew]))
    ifFalse:[^ false].
    LastModule := module.

    (self checkForExistingModule:module directory:directory using:mgr allowCreate:(createDirs or:[creatingNew]))
    ifFalse:[^ false].
    LastPackage := directory.

    "/
    "/ check for the container itself
    "/
    (mgr checkForExistingContainer:fileName inModule:module directory:directory) ifTrue:[
        creatingNew ifTrue:[
            self warn:(resources string:'Container for %1 already exists in %2/%3.' with:fileName with:module with:directory) withCRs.
        ].

"/            (oldModule notNil
"/            and:[(oldModule ~= module)
"/                 or:[oldPackage ~= package
"/                 or:[oldFileName ~= fileName]]])
"/            ifFalse:[
"/                self warn:(resources string:'no change').
"/                ^ false.
"/            ].

        doCheckinWithoutAsking ifFalse:[
            (Dialog 
                confirm:(resources string:'check %1 into the existing container

    %2 / %3 / %4  ?'
                                with:className
                                with:module 
                                with:directory 
                                with:fileName) withCRs
                noLabel:'Cancel') 
            ifFalse:[
                ^ false.
            ].  
        ].  

        aClass updateVersionMethodFor:'$' , 'Header' , '$'. "/ concatenated to avoid RCS-expansion

        oldFileName notNil ifTrue:[
            msg := ('forced checkin / source container change from ' , oldFileName).
        ] ifFalse:[
            msg := 'defined source container'
        ].

        (forceCheckIn := doCheckinWithoutAsking) ifFalse:[
            (mgr
                checkinClass:aClass 
                fileName:fileName 
                directory:directory 
                module:module 
                logMessage:msg)
            ifFalse:[
                doCheckinWithoutAsking ifFalse:[
                    (Dialog 
                        confirm:'No easy merge seems possible; force checkin (no merge) ?'
                        noLabel:'Cancel') 
                    ifFalse:[
                        ^ false.
                    ].
                ].
                forceCheckIn := true.
            ]
        ].
        forceCheckIn ifTrue:[
            (mgr
                checkinClass:aClass 
                fileName:fileName 
                directory:directory 
                module:module 
                logMessage:msg
                force:true)
            ifFalse:[
                self warn:(resources string:'Failed to check into existing container.').
                ^ false.
            ].
        ].
        ^ true
    ] ifFalse:[
        (createContainer or:[creatingNew]) ifFalse:[
            (Dialog
                 confirm:(resources string:'No container exists for %1 in %2/%3\\create ?' 
                                      with:fileName with:module with:directory) withCRs
                 noLabel:'Cancel') ifFalse:[
                ^ false
            ]
        ]
    ].

    aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | mthd setPackage:requiredPackage].
    aClass package:requiredPackage.

    (mgr
            createContainerFor:aClass
            inModule:module
            package:directory
            container:fileName) ifFalse:[
        self warn:(resources string:'Failed to create container.').
        ^ false.
    ].
    ^ true

    "Modified: / 25-10-2006 / 11:12:22 / cg"
!

removeSourceContainerForClass:aClass
    "show container & let user confirm twice."

    ^ self removeSourceContainerForClass:aClass confirm:true warn:true
!

removeSourceContainerForClass:aClass confirm:doConfirm warn:doWarn
    "show container & optionally let user confirm twice."

    |module directory fileName info mgr resources|

    resources := self classResources.

    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 := mgr sourceInfoOfClass:aClass.
    info notNil ifTrue:[
        (info includesKey:#module) ifTrue:[
            module := (info at:#module).
        ].
        (info includesKey:#directory) ifTrue:[
            directory := (info at:#directory).
        ].
        fileName := mgr containerFromSourceInfo:info.
    ].

    module isNil ifTrue:[
        doWarn ifTrue:[
            self warn:(resources stringWithCRs:'classes module is unknown.\\It seems to not have a container.') .
        ].
        ^ false.
    ].
    directory isNil ifTrue:[
        doWarn ifTrue:[
            self warn:(resources stringWithCRs:'classes package is unknown.\\It seems to not have a container.') .
        ].
        ^ false.
    ].
    fileName isNil ifTrue:[
        doWarn ifTrue:[
            self warn:(resources stringWithCRs:'classes container fileName is unknown.\\It seems to not have a container.') .
        ].
        ^ false.
    ].

    OperatingSystem isMSDOSlike ifTrue:[
        "cvs expects unix-filenames"
        module := module copy replaceAll:$\ with:$/.
        directory := directory copy replaceAll:$\ with:$/.
    ].
    (mgr checkForExistingContainer:fileName inModule:module directory:directory) ifFalse:[
        doWarn ifTrue:[
            self warn:(resources stringWithCRs:'Class has no source container.') .
        ].
        ^ false.
    ].

    doConfirm ifTrue:[
        (Dialog
            choose:(resources 
                        stringWithCRs:'Please confirm removal of the container for %1:

container:    %2 / %3 / %4

Really remove ?' 
                        with:aClass name 
                        with:module 
                        with:directory 
                        with:fileName) 
            labels:(Array 
                        with:(resources string:'No') 
                        with:(resources string:'Remove'))
            values:#(false true)
            default:false) ifFalse:[
            ^ false.
        ].
    ].

    (mgr removeContainerFor:aClass
                   inModule:module
                    package:directory
                  container:fileName) ifFalse:[
        doWarn ifTrue:[
            self warn:(resources string:'failed to remove container.').
        ].
        ^ true.
    ].
    ^ false

    "Modified: / 13-09-2006 / 18:25:48 / cg"
!

repositoryLogOf:aClass onto:aStream
    |info rv mgr info2 module fn msg s|

    info := aClass revisionInfo.

    rv := aClass binaryRevision.
    rv notNil ifTrue:[
        aStream nextPutLine:'**** Loaded classes binary information ****'; cr.
        aStream nextPutLine:'  Binary based upon : ' , rv.
        aStream cr.
    ].

    info notNil ifTrue:[
        (info includesKey:#revision) ifFalse:[
            aStream nextPutLine:'WARNING:'; cr.
            aStream nextPutLine:'  The class seems not to be loaded from the repository.'.
            aStream nextPutLine:'  Check carefully before checking anything in.'.
            aStream nextPutLine:'  (i.e. compare with repository for renamed class(es), same-name but unrelated etc.)'.
            aStream cr.
        ].

        aStream nextPutLine:'**** Classes source information ****'; cr.
        s := info at:#repositoryPath ifAbsent:nil.
        s notNil ifTrue:[
            aStream nextPutLine:'  Source repository : ' , s
        ].
        aStream nextPutLine:'  Filename ........ : ' , (info at:#fileName ifAbsent:'?').
        aStream nextPutLine:'  Revision ........ : ' , (info at:#revision ifAbsent:'?').
        aStream nextPutLine:'  Checkin date .... : ' , (info at:#date ifAbsent:'?') , ' ' , 
                                                       (info at:#time ifAbsent:'?'), ' ', 
                                                       (info at:#timezone ifAbsent:'').
        aStream nextPutLine:'  Checkin user .... : ' , (info at:#user ifAbsent:'?').

        (info2 := aClass packageSourceCodeInfo) notNil ifTrue:[
            aStream nextPutLine:'  Repository: ..... : ' , (info2 at:#module ifAbsent:'?').
            aStream nextPutLine:'  Directory: ...... : ' , (info2 at:#directory ifAbsent:'?').
        ].
        aStream nextPutLine:'  Container ....... : ' , (info at:#repositoryPathName ifAbsent:'?').
        aStream cr.

        mgr := self sourceCodeManagerFor:aClass.
        mgr notNil ifTrue:[
            aStream nextPutLine:'**** Repository information ****'; cr.

            module := info2 at:#module ifAbsent:nil.
            module notNil ifTrue:[
                aStream nextPutLine:('  CVS Root ......: ' , 
                                    ((mgr repositoryNameForModule:module) ifNil:[mgr repositoryName , ' (default)'])).
            ].
            mgr writeRevisionLogOf:aClass to:aStream.
        ]
    ] ifFalse:[
        aStream nextPutLine:'No revision info found'.
        aClass isLoaded ifFalse:[
            aStream cr; nextPutAll:'This is an autoloaded class - you may see more after it is loaded.'
        ] ifTrue:[
            fn := aClass classFilename.
            aClass wasAutoloaded ifTrue:[
                msg := 'This class was autoloaded.'.
                msg := msg , ' (from ''' , fn , ''')'.
            ] ifFalse:[
                msg := 'This class was loaded from ''' , fn , '''.'
            ].
            msg notNil ifTrue:[
                aStream cr; nextPutAll:msg.
            ]
        ]
    ]

    "Modified: / 06-10-2006 / 13:25:22 / cg"
!

tagClass:aClass as:tag
    |mgr|

    mgr := self sourceCodeManagerFor:aClass.
    mgr
        setSymbolicName:tag 
        revision:nil 
        overWrite:true 
        class:aClass.

    "Modified: / 12-09-2006 / 13:03:59 / cg"
!

tagClasses:aCollectionOfClasses as:tag
    |classesPerManager|

    classesPerManager := Dictionary new.
    aCollectionOfClasses 
        do:[:eachClass | 
            |manager|

            manager := self sourceCodeManagerFor:eachClass.
            (classesPerManager at:manager ifAbsentPut:[Set new]) add:eachClass
        ].

    classesPerManager keysAndValuesDo:[:manager :classesPerManager|
        manager
            setSymbolicName:tag 
            revision:nil 
            overWrite:true 
            classes:classesPerManager.
    ].
    ^ true

    "Created: / 12-09-2006 / 13:04:29 / cg"
!

tagPath:aPath as:tag using:aManager
    aManager 
        setSymbolicName:tag 
        revision:nil 
        overWrite:true 
        path:aPath.

    "Modified: / 12-09-2006 / 12:04:44 / cg"
! !

!SourceCodeManagerUtilities class methodsFor:'utilities-cvs-helpers'!

getMethodVersionsOfClass:aClass selector:selector numberOfRevisions:numberOfRevisionsOrNil
    "check-out all previous versions of aClass and retrieve the history of selector.
     Return a dictionary associating revision with a changeList entries for that method.
     Unfinished - need a GUI for that."

    |mgr theClass revisionLog revisions items s entriesPerRevision previousVersion|

    theClass := aClass theNonMetaclass.

    mgr := self sourceCodeManagerFor:theClass.
    mgr isNil ifTrue:[
        self error:'no sourceCodeManager'.
    ].

    revisionLog := mgr
                        revisionLogOf:theClass
                        numberOfRevisions:numberOfRevisionsOrNil.

    revisions := revisionLog at:#revisions.
    items := revisions collect:[:each | |rev date who|
                                    rev := each at:#revision.
                                    date := each at:#date.
                                    who := each at:#author.
                                    rev allBold , ' [' , date , ' by ' , who , ']'
                               ].

    revisions := revisions collect:[:each | each at:#revision].
    revisions addFirst:#current.
    entriesPerRevision := Dictionary new.

    previousVersion := nil.
    revisions reverseDo:[:eachRevision |
        |srcStream entries thisVersion|

        eachRevision == #current ifTrue:[
            s := '' writeStream.
            theClass fileOutOn:s withTimeStamp:false.
            srcStream := s contents readStream.
        ] ifFalse:[
            self activityNotification:('checking out revision ' , eachRevision , '...').
            srcStream := mgr getSourceStreamFor:theClass revision:eachRevision.
        ].

        entries := ChangeSet fromStream:srcStream.
        srcStream close.

        "/ remove all definitions       
        entries := entries select:[:each | each isMethodChange].
        "/ remove all methods which are for other selectors      
        entries := entries select:[:each | each selector == selector].
        "/ remove all methods which are for private subclasses      
        entries := entries select:[:each | each className = aClass name].

        entries size == 1 ifTrue:[
            "/ the method is there
            thisVersion := entries first.
            (previousVersion notNil and:[previousVersion sameAs:thisVersion]) ifTrue:[
                "/ no change
            ] ifFalse:[
                entriesPerRevision at:eachRevision put:thisVersion.
            ].
        ] ifFalse:[
            "/ the method is not there
        ].
        previousVersion := thisVersion.
    ].
    self error:'unfinished code'.

    "
     self getMethodVersionsOfClass:MenuPanel selector:#'helpTextForItem:' numberOfRevisions:20
     self getMethodVersionsOfClass:NewLauncher class selector:#'menu' numberOfRevisions:20
    "
! !

!SourceCodeManagerUtilities class methodsFor:'utilities-cvs-user interaction'!

askForContainer:boxText title:title note:notice initialModule:initialModule initialPackage:initialPackage initialFileName:initialFileName
    "open a dialog asking for a source container;
     return a dictionary containing module, package and filename,
     or nil if canceled."

    ^ self
        askForContainer:boxText title:title note:notice 
        initialModule:initialModule initialPackage:initialPackage initialFileName:initialFileName 
        forNewContainer:true
!

askForContainer:boxText title:title note:notice initialModule:initialModule initialPackage:initialPackage initialFileName:initialFileName forNewContainer:forNewContainer
    "open a dialog asking for a source container;
     return a dictionary containing module, package and filename,
     or nil if canceled."

    |box y component resources answer
     moduleHolder packageHolder fileNameHolder
     module package fileName 
     knownContainers knownPackages packageUpdater
     packageBoxComponent fileNameBoxComponent fileNameUpdater|

    knownContainers := Set new.
    Smalltalk allClassesDo:[:cls | |pckg|
        pckg := cls package.
        pckg size > 0 ifTrue:[
            knownContainers add:(pckg upTo:$:)
        ]
    ].
    knownContainers := knownContainers asOrderedCollection.
    knownContainers := knownContainers select:[:module | module isBlank not].
    knownContainers sort.

    packageUpdater := [
        |theModulePrefix|

        theModulePrefix := moduleHolder value , ':'.

        Cursor wait showWhile:[
            knownPackages := Set new.
            Smalltalk allClassesDo:[:cls | |pckg idx|
                pckg := cls package.
                pckg size > 0 ifTrue:[
                    (pckg startsWith:theModulePrefix) ifTrue:[
                        idx := pckg indexOf:$:.
                        knownPackages add:(pckg copyFrom:idx + 1)
                    ]
                ]
            ].
            knownPackages := knownPackages asOrderedCollection.
            knownPackages := knownPackages select:[:package | package isBlank not].
            knownPackages sort.
            packageBoxComponent list:knownPackages.
        ].
    ].

    fileNameUpdater := [
        |module package files|

        Cursor read showWhile:[
            module := moduleHolder value ? (Project noProjectID).
            package := packageHolder value ? (Project noProjectID).

            files := SourceCodeManager getExistingContainersInModule:module directory:package.
            files := files asOrderedCollection.
            files := files select:[:eachFile | eachFile asFilename hasSuffix:'st'].
            files sort.
            fileNameBoxComponent list:files.
        ].
    ].

    moduleHolder := initialModule asValue.
    packageHolder := initialPackage asValue.
    fileNameHolder := initialFileName asValue.

    resources := self classResources.

    "/
    "/ open a dialog for this
    "/
    box := DialogBox new.
    box label:title.

    component := box addTextLabel:boxText withCRs.
    component adjust:#left; borderWidth:0.
    box addVerticalSpace.
    box addVerticalSpace.

    y := box yPosition.
    component := box addTextLabel:(resources string:'Module:').
    component width:0.4; adjust:#right.
    box yPosition:y.
    component := box addComboBoxOn:moduleHolder tabable:true.
    component list:knownContainers.

"/    component := box addInputFieldOn:moduleHolder tabable:true.
    component width:0.6; left:0.4; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.

    box addVerticalSpace.
    y := box yPosition.
    component := box addTextLabel:(resources string:'Package:').
    component width:0.4; adjust:#right.
    box yPosition:y.
    packageBoxComponent := component := box addComboBoxOn:packageHolder tabable:true.
"/    component := box addInputFieldOn:packageHolder tabable:true.
    component width:0.6; left:0.4; "immediateAccept:true; "acceptOnLeave:true; cursorMovementWhenUpdating:#beginOfLine.
    packageUpdater value.
    moduleHolder onChangeEvaluate:packageUpdater.

    box addVerticalSpace.
    y := box yPosition.
    component := box addTextLabel:(resources string:'Filename:').
    component width:0.4; adjust:#right.
    box yPosition:y.

    forNewContainer ifTrue:[
        component := box addInputFieldOn:fileNameHolder tabable:true.
        component width:0.6; left:0.4; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
    ] ifFalse:[
        fileNameBoxComponent := component := box addComboBoxOn:fileNameHolder tabable:true.
        component width:0.6; left:0.4; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
        fileNameUpdater value.
        packageHolder onChangeEvaluate:fileNameUpdater.
    ].

    box addVerticalSpace.

    notice notNil ifTrue:[
        component := box addTextLabel:notice.
        component adjust:#left; borderWidth:0.
    ].

    box addVerticalSpace.
    box addAbortAndOkButtons.

    (YesToAllNotification notNil and:[YesToAllNotification isHandled]) ifTrue:[
        component := Button label:'Yes to all'.
        component action:[
                            YesToAllNotification queryWith:true.
                            box doAccept.
                         ].
        (DialogBox defaultOKButtonAtLeft) ifTrue:[
            box addButton:component after:nil.
        ] ifFalse:[
            box addButton:component before:nil.
        ].
    ].
    (AbortAllSignal isHandled) ifTrue:[
        component := Button label:'Cancel all'.
        component action:[
                            box hide.
                            AbortAllSignal raiseSignal.
                         ].
        (DialogBox defaultOKButtonAtLeft) ifTrue:[
            box addButton:component before:nil.
        ] ifFalse:[
            box addButton:component after:nil.
        ].
    ].

    (YesToAllQuery notNil and:[YesToAllQuery isHandled]) ifTrue:[
        answer := YesToAllQuery query.
    ].

    answer isNil ifTrue:[
        box showAtPointer.
        answer := box accepted
    ].

    box destroy.
    answer ifFalse:[
        ^ nil
    ].

    module := moduleHolder value withoutSpaces.
    package := packageHolder value withoutSpaces.
    fileName := fileNameHolder value withoutSpaces.
    ^ Dictionary new
        at:#module put:module;
        at:#package put:package;
        at:#fileName put:fileName;
        yourself

    "
     self 
        askForContainer:'enter container' title:'container' note:'some note'
        initialModule:'foo' initialPackage:'bar' initialFileName:'baz'        
    "

    "Modified: / 23-08-2006 / 14:13:04 / cg"
!

askForExistingRevision:boxText title:title class:aClass
    "open a dialog asking for a containers revision;
     return a revision number, or nil if canceled."

    |mgr sourceInfo module package fileName|

    mgr := self sourceCodeManagerFor:aClass.
    sourceInfo := mgr sourceInfoOfClass:aClass.
    sourceInfo isNil ifTrue:[^ nil].

    package := mgr directoryFromSourceInfo:sourceInfo.
    module := mgr moduleFromSourceInfo:sourceInfo.  
    fileName := mgr containerFromSourceInfo:sourceInfo.
    ^ self
        askForExistingRevision:boxText 
        title:title 
        class:aClass 
        manager:mgr 
        module:module package:package fileName:fileName

    "
     SourceCodeManagerUtilities
        askForRevisionToCompare:'enter revision'
        title:'revision'
        class:Array
    "

    "Modified: / 12-09-2006 / 14:17:04 / cg"
!

askForExistingRevision:boxText title:title class:clsOrNil manager:aSourceCodeManager module:module package:directory fileName:fileName
    "open a dialog asking for a containers revision;
     return a revision number, or nil if canceled."

    |partialLog revisions items newestRev
     box y component resources 
     revisionHolder symbolicNames stableRevision releasedRevision|

    partialLog := aSourceCodeManager
        revisionLogOf:clsOrNil
        numberOfRevisions:20
        fileName:fileName
        directory:directory 
        module:module.

    partialLog notNil ifTrue:[
        newestRev := partialLog at:#newestRevision.
        revisions := partialLog at:#revisions.
        symbolicNames := partialLog at:#symbolicNames ifAbsent:[].
        symbolicNames notNil ifTrue:[
            stableRevision := symbolicNames at:'stable' ifAbsent:[].
            releasedRevision := symbolicNames at:'released' ifAbsent:[].
        ].
            
        items := revisions collect:[:each | |rev date who flag|
                                        rev := each at:#revision.
                                        date := each at:#date.
                                        who := each at:#author.
                                        rev = stableRevision ifTrue:[
                                            flag := ' Stable' allBold.
                                        ] ifFalse:[rev = releasedRevision ifTrue:[
                                            flag := ' Released' allBold.
                                        ] ifFalse:[
                                            flag := ' '
                                        ]].
                                        rev allBold , flag, ' [' , date , ' by ' , who , ']'
                                   ].
        revisions := revisions collect:[:each | each at:#revision].
    ] ifFalse:[
        newestRev := aSourceCodeManager newestRevisionInFile:fileName directory:directory module:module.
        revisions := items := nil.

        newestRev isNil ifTrue:[
            (aSourceCodeManager checkForExistingContainer:fileName inModule:module directory:directory)
            ifFalse:[
                self warn:'Could not find/access the container for ',fileName,' in the repository.
This could be due to:
    - invalid/wrong CVS-Root setting
    - missing CVS access rights
        (no access / not logged in)
    - changed CVSRoot after compilation
        (i.e. wrong CVS-path in classes version method)
'.
                ^ nil
            ]
        ]
    ].
    revisionHolder  := newestRev asValue.
    resources := self classResources.

    revisionHolder onChangeEvaluate:[
        "/ cut off everything after revision
        |s first words|

        s := revisionHolder value.
        words := s asCollectionOfWords.
        words size > 0 ifTrue:[
            first := words first string.
            first ~= s ifTrue:[
                revisionHolder value:first
            ]
        ]
    ].

    "/
    "/ open a dialog for this
    "/
    box := DialogBox new.
    box label:title.

    component := box addTextLabel:boxText withCRs.
    component adjust:#left; borderWidth:0.
    box addVerticalSpace.
    box addVerticalSpace.

    y := box yPosition.
    component := box addTextLabel:(resources string:'Revision:').
    component width:0.4; adjust:#right.
    box yPosition:y.
    component := box addComboBoxOn:revisionHolder tabable:true.
    component list:items.
    component width:0.6; left:0.4; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.

    box addVerticalSpace.

    box addAbortAndOkButtons.

    Object abortAllSignal isHandled ifTrue:[
        (box addAbortButtonLabelled:'Cancel all') action:[AbortAllSignal raise].
    ].

    box showAtPointer.

    box accepted ifFalse:[
        box destroy.
        ^ nil
    ].
    box destroy.

    ^ revisionHolder value withoutSpaces.

    "
     SourceCodeManagerUtilities
        askForRevisionToCompare:'enter revision'
        title:'revision'
        class:nil
        manager:SourceCodeManager 
        module:'stx'
        directory:'libbasic'
        fileName:'Array.st'
    "

    "Modified: / 13-09-2006 / 18:24:46 / cg"
!

checkAndWarnAboutBadMessagesInClass:aClass checkAgainHolder:checkAgainHolder
    "check if a class contains message-sends to:
        #halt
        #halt:
        #error
        (and maybe more in the future)"

    |badStuff whatIsBad msg answer labels values defaultAnswer dontShowAgain|

    badStuff := #(
        ( halt         'sent of #halt (use for debugging only) - better use #error:''some message''' )
        ( halt:        'sent of #halt: (use for debugging only) - better use #error:' )
        ( error        'sent of #error without descriptive message - better use #error:''some message''' )
    ).

    whatIsBad := Set new.
    aClass theNonMetaclass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
        |setOfLiterals setOfSentMessages|

        setOfLiterals := mthd literals.  "/ try without parsing first.
        (badStuff contains:[:eachEntry | setOfLiterals includes:eachEntry first]) ifTrue:[
            setOfSentMessages := mthd messagesSent.
            badStuff do:[:eachEntry |
                (setOfSentMessages includes:eachEntry first) ifTrue:[
                    whatIsBad add:eachEntry second
                ]
            ].
        ].
    ].
    whatIsBad notEmpty ifTrue:[
        (YesToAllQuery notNil and:[YesToAllQuery isHandled]) ifTrue:[
            answer := YesToAllQuery query.
            answer notNil ifTrue:[ ^ answer ].
        ].

        msg := '%1 contains the following  (considered bad style) message sends:\\'.
        whatIsBad do:[:each |
            msg := msg , '   ' , each , '\'
        ].
        msg := msg , '\\' , 'Do you really want to checkIn the %1 class ?'.
        msg := msg bindWith:aClass name.

        (YesToAllNotification notNil and:[YesToAllNotification isHandled]) ifTrue:[
            labels := #('Cancel All' 'Cancel' 'No to All' 'No' 'Yes to All' 'Yes') "#('Yes' 'Yes to All' 'No' 'No to All' 'Cancel')".
            values := #(#cancelAll nil #noToAll false #yesToAll true) "#(true #yesToAll false #noToAll nil)".
            defaultAnswer := #yesToAll.
        ] ifFalse:[
            labels := #('No' 'Yes').
            values := #(false true).
            defaultAnswer := true.
        ].

"/        AbortAllOperationRequest isHandled ifTrue:[
"/            labels := #('Cancel All') , labels.
"/            values := #(#cancelAll) , values.
"/        ].

        DialogBox aboutToOpenBoxNotificationSignal handle:[:ex |
            |box|

            checkAgainHolder isValueModel ifTrue:[
                dontShowAgain := checkAgainHolder value not asValue.
                box := ex parameter.
                box verticalPanel 
                    add:(CheckBox label:'Do not show this Dialog again.'
                                  model:dontShowAgain).
            ].
            ex proceed.
        ] do:[
            answer := OptionBox 
                          request:msg withCRs
                          label:'Really checkIn ?'
                          image:(InfoBox iconBitmap)
                          buttonLabels:labels
                          values:values
                          default:defaultAnswer
                          onCancel:nil.
        ].
        answer isNil ifTrue:[
            AbortSignal raise.
        ].

        dontShowAgain notNil ifTrue:[
            checkAgainHolder value:dontShowAgain value not 
        ].

        answer == #cancelAll ifTrue:[
            AbortAllSignal raise.
        ].

        answer == #yesToAll ifTrue:[
            YesToAllNotification queryWith:true.
            ^ true
        ].
        answer == #noToAll ifTrue:[
            YesToAllNotification queryWith:false.
            ^ false
        ].
        ^ answer
    ].
    ^ true.

    "
     self checkAndWarnAboutBadMessagesInClass:(SourceCodeManagerUtilities)  
    "
!

getCheckinInfoFor:aString initialAnswer:initialAnswerOrNil
    "get a log message for checking in a class.
     Return the message or nil if aborted."

    ^ self
        getCheckinInfoFor:aString 
        initialAnswer:initialAnswerOrNil
        withQuickOption:false

    "
     SourceCodeManagerUtilities getCheckinInfoFor:'hello' initialAnswer:'bla'
    "

    "Modified: / 22-06-2006 / 12:49:30 / cg"
!

getCheckinInfoFor:aString initialAnswer:initialAnswerOrNil withQuickOption:withQuickOption
    "get a log message for checking in a class.
     Return the message or nil if aborted."

    |logMsg info|

    info := Tools::CheckinInfoDialog 
                getCheckinInfoFor:aString 
                initialAnswer:(initialAnswerOrNil ? LastSourceLogMessage)
                withQuickOption:withQuickOption.
    info notNil ifTrue:[
        logMsg := info logMessage.
        logMsg notNil ifTrue:[
            LastSourceLogMessage := logMsg
        ].
    ].
    ^ info

    "
     SourceCodeManagerUtilities getCheckinInfoFor:'hello' initialAnswer:'bla'
    "

    "Modified: / 22-06-2006 / 12:49:30 / cg"
! !

!SourceCodeManagerUtilities class methodsFor:'utilities-encoding'!

guessEncodingOfBuffer:buffer
    "look for a string of the form
            encoding #name
     or:
            encoding: name
     within the given buffer 
     (which is usually the first few bytes of a textFile)."

    <resource: #obsolete>

    self obsoleteMethodWarning:'ask CharacterEncoder'.
    ^ CharacterEncoder guessEncodingOfBuffer:buffer
!

guessEncodingOfFile:aFilename
    "look for a string
        encoding #name
     or:
        encoding: name
     within the given buffer 
     (which is usually the first few bytes of a textFile).
     If thats not found, use heuristics (in CharacterArray) to guess."

    <resource: #obsolete>

    self obsoleteMethodWarning:'ask CharacterEncoder'.
    ^ CharacterEncoder guessEncodingOfFile:aFilename

    "
     SourceCodeManagerUtilities guessEncodingOfFile:'../../libview2/resources/ApplicationModel_de.rs' asFilename
     SourceCodeManagerUtilities guessEncodingOfFile:'../../libview2/resources/ApplicationModel_ru.rs' asFilename
    "
!

guessEncodingOfStream:aStream
    "look for a string of the form
            encoding #name
     or:
            encoding: name
     in the first few bytes of aStream."

    <resource: #obsolete>

    self obsoleteMethodWarning:'ask CharacterEncoder'.
    ^ CharacterEncoder guessEncodingOfStream:aStream
! !

!SourceCodeManagerUtilities class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic3/SourceCodeManagerUtilities.st,v 1.152 2006-11-16 11:12:33 fm Exp $'
! !